Skip to content

Commit b1424d8

Browse files
committed
Move utilities from .Common to new Utils module (formal API change)
1 parent 0dc80f5 commit b1424d8

File tree

6 files changed

+93
-39
lines changed

6 files changed

+93
-39
lines changed

lib/Text/Regex/TDFA/Common.hs

Lines changed: 1 addition & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ import Data.Sequence as S(Seq)
2121
--import Debug.Trace
2222

2323
import Text.Regex.TDFA.IntArrTrieSet(TrieSet)
24+
import Utils
2425

2526
{-# INLINE look #-}
2627
look :: Int -> IntMap a -> a
@@ -30,43 +31,6 @@ common_error :: String -> String -> a
3031
common_error moduleName message =
3132
error ("Explict error in module "++moduleName++" : "++message)
3233

33-
on :: (t1 -> t1 -> t2) -> (t -> t1) -> t -> t -> t2
34-
f `on` g = (\x y -> (g x) `f` (g y))
35-
36-
-- | After 'sort' or 'sortBy' the use of 'nub' or 'nubBy' can be replaced by 'norep' or 'norepBy'.
37-
norep :: (Eq a) => [a]->[a]
38-
norep [] = []
39-
norep x@[_] = x
40-
norep (a:bs@(c:cs)) | a==c = norep (a:cs)
41-
| otherwise = a:norep bs
42-
43-
-- | After 'sort' or 'sortBy' the use of 'nub' or 'nubBy' can be replaced by 'norep' or 'norepBy'.
44-
norepBy :: (a -> a -> Bool) -> [a] -> [a]
45-
norepBy _ [] = []
46-
norepBy _ x@[_] = x
47-
norepBy eqF (a:bs@(c:cs)) | a `eqF` c = norepBy eqF (a:cs)
48-
| otherwise = a:norepBy eqF bs
49-
50-
mapFst :: (Functor f) => (t -> t2) -> f (t, t1) -> f (t2, t1)
51-
mapFst f = fmap (\ (a,b) -> (f a,b))
52-
53-
mapSnd :: (Functor f) => (t1 -> t2) -> f (t, t1) -> f (t, t2)
54-
mapSnd f = fmap (\ (a,b) -> (a,f b))
55-
56-
fst3 :: (a,b,c) -> a
57-
fst3 (x,_,_) = x
58-
59-
snd3 :: (a,b,c) -> b
60-
snd3 (_,x,_) = x
61-
62-
thd3 :: (a,b,c) -> c
63-
thd3 (_,_,x) = x
64-
65-
flipOrder :: Ordering -> Ordering
66-
flipOrder GT = LT
67-
flipOrder LT = GT
68-
flipOrder EQ = EQ
69-
7034
noWin :: WinTags -> Bool
7135
noWin = null
7236

lib/Text/Regex/TDFA/CorePattern.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ import Data.Semigroup as Sem
4949

5050
import Text.Regex.TDFA.Common {- all -}
5151
import Text.Regex.TDFA.Pattern(Pattern(..),starTrans)
52+
import Utils
5253
-- import Debug.Trace
5354

5455
{- By Chris Kuklewicz, 2007. BSD License, see the LICENSE file. -}

lib/Text/Regex/TDFA/TDFA.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ import qualified Text.Regex.TDFA.IntArrTrieSet as Trie(lookupAsc,fromSinglesMerg
2828
import Text.Regex.TDFA.Pattern(Pattern)
2929
--import Text.Regex.TDFA.RunMutState(toInstructions)
3030
import Text.Regex.TDFA.TNFA(patternToNFA)
31+
import Utils
3132
--import Debug.Trace
3233

3334
{- By Chris Kuklewicz, 2007. BSD License, see the LICENSE file. -}

lib/Text/Regex/TDFA/TNFA.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,11 +55,12 @@ import qualified Data.Set as S (insert, toAscList)
5555
import Text.Regex.TDFA.Common(QT(..),QNFA(..),QTrans,TagTask(..),TagUpdate(..),DoPa(..)
5656
,CompOption(..)
5757
,Tag,TagTasks,TagList,Index,WinTags,GroupIndex,GroupInfo(..)
58-
,common_error,noWin,snd3,mapSnd)
58+
,common_error,noWin)
5959
import Text.Regex.TDFA.CorePattern(Q(..),P(..),OP(..),WhichTest,cleanNullView,NullView
6060
,SetTestInfo(..),Wanted(..),TestInfo
6161
,mustAccept,cannotAccept,patternToQ)
6262
import Text.Regex.TDFA.Pattern (Pattern(..), decodePatternSet)
63+
import Utils
6364

6465
ecart :: String -> a -> a
6566
ecart _ = id

lib/Utils.hs

Lines changed: 83 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,83 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE RankNTypes #-}
3+
4+
-- | Internal module for utilities used in the implementation.
5+
6+
module Utils (module Utils, module X) where
7+
8+
import Control.Applicative (Const(..))
9+
import Control.Applicative as X ((<*>))
10+
import Control.Monad.Identity
11+
import Data.Foldable as X (foldMap)
12+
import Data.Functor as X
13+
import Data.Monoid as X (Monoid(..))
14+
import Data.Semigroup as X (Semigroup(..))
15+
16+
-- * Lenses
17+
---------------------------------------------------------------------------
18+
19+
type Lens' o i = forall f. Functor f => (i -> f i) -> (o -> f o)
20+
21+
type LensGet o i = o -> i
22+
type LensSet o i = i -> o -> o
23+
type LensMap o i = (i -> i) -> o -> o
24+
25+
infixl 8 ^.
26+
-- | Get inner part @i@ of structure @o@ as designated by @Lens' o i@.
27+
(^.) :: o -> Lens' o i -> i
28+
o ^. l = getConst $ l Const o
29+
30+
-- | Set inner part @i@ of structure @o@ as designated by @Lens' o i@.
31+
set :: Lens' o i -> LensSet o i
32+
set l = over l . const
33+
34+
-- | Modify inner part @i@ of structure @o@ using a function @i -> i@.
35+
over :: Lens' o i -> LensMap o i
36+
over l f o = runIdentity $ l (Identity . f) o
37+
38+
-- * Misc
39+
---------------------------------------------------------------------------
40+
41+
#if !MIN_VERSION_base(4,7,0)
42+
($>) :: Functor f => f a -> b -> f b
43+
($>) = flip (<$)
44+
#endif
45+
46+
#if !MIN_VERSION_base(4,11,0)
47+
(<&>) :: Functor f => f a -> (a -> b) -> f b
48+
(<&>) = flip fmap
49+
#endif
50+
51+
-- | After 'sort' or 'sortBy' the use of 'nub' or 'nubBy' can be replaced by 'norep' or 'norepBy'.
52+
norep :: (Eq a) => [a]->[a]
53+
norep [] = []
54+
norep x@[_] = x
55+
norep (a:bs@(c:cs)) | a==c = norep (a:cs)
56+
| otherwise = a:norep bs
57+
58+
-- | After 'sort' or 'sortBy' the use of 'nub' or 'nubBy' can be replaced by 'norep' or 'norepBy'.
59+
norepBy :: (a -> a -> Bool) -> [a] -> [a]
60+
norepBy _ [] = []
61+
norepBy _ x@[_] = x
62+
norepBy eqF (a:bs@(c:cs)) | a `eqF` c = norepBy eqF (a:cs)
63+
| otherwise = a:norepBy eqF bs
64+
65+
mapFst :: (Functor f) => (t -> t2) -> f (t, t1) -> f (t2, t1)
66+
mapFst f = fmap (\ (a,b) -> (f a,b))
67+
68+
mapSnd :: (Functor f) => (t1 -> t2) -> f (t, t1) -> f (t, t2)
69+
mapSnd f = fmap (\ (a,b) -> (a,f b))
70+
71+
fst3 :: (a,b,c) -> a
72+
fst3 (x,_,_) = x
73+
74+
snd3 :: (a,b,c) -> b
75+
snd3 (_,x,_) = x
76+
77+
thd3 :: (a,b,c) -> c
78+
thd3 (_,_,x) = x
79+
80+
flipOrder :: Ordering -> Ordering
81+
flipOrder GT = LT
82+
flipOrder LT = GT
83+
flipOrder EQ = EQ

regex-tdfa.cabal

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,8 @@ library
8484
Text.Regex.TDFA.Text
8585
Text.Regex.TDFA.Text.Lazy
8686

87-
other-modules: Paths_regex_tdfa
87+
other-modules: Utils
88+
Paths_regex_tdfa
8889

8990
-- Support Semigroup instances uniformly
9091
--
@@ -105,6 +106,8 @@ library
105106
, parsec == 3.1.*
106107
, regex-base == 0.94.*
107108
, text >= 1.2.3 && < 2.1
109+
, transformers >= 0.2.2.1 && < 0.7
110+
-- For Control.Monad.Identity across GHC versions
108111

109112
default-language: Haskell2010
110113
default-extensions: BangPatterns
@@ -123,6 +126,7 @@ library
123126
UnboxedTuples
124127
UnliftedFFITypes
125128
other-extensions: CPP
129+
RankNTypes
126130

127131
ghc-options: -Wall -funbox-strict-fields -fspec-constr-count=10 -fno-warn-orphans
128132

0 commit comments

Comments
 (0)