File: Replace.lhs

package info (click to toggle)
haskell-regex 1.1.0.2-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 424 kB
  • sloc: haskell: 4,533; makefile: 3
file content (539 lines) | stat: -rw-r--r-- 16,509 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
\begin{code}
{-# LANGUAGE NoImplicitPrelude          #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE MonoLocalBinds             #-}

module Text.RE.ZeInternals.Replace
  (
  -- * REContext and RELocation
    REContext(..)
  , RELocation(..)
  , isTopLocation
  -- * replaceAll
  , replaceAll
  , replaceAllCaptures
  , replaceAllCaptures_
  , replaceAllCapturesM
  -- * replace
  , replace
  , replaceCaptures
  , replaceCaptures_
  , replaceCapturesM
  -- * expandMacros
  , expandMacros
  , expandMacros'
  -- * templateCaptures
  , templateCaptures
  -- * Replace and ReplaceMethods
  , Replace(..)
  , ReplaceMethods(..)
  , replaceMethods
  ) where

import           Control.Applicative
import           Data.Array
import qualified Data.ByteString.Char8          as B
import qualified Data.ByteString.Lazy.Char8     as LBS
import           Data.Char
import qualified Data.Foldable                  as F
import           Data.Functor.Identity
import qualified Data.HashMap.Strict            as HM
import           Data.Maybe
import qualified Data.Monoid                    as M
import qualified Data.Sequence                  as S
import qualified Data.Text                      as T
import qualified Data.Text.Encoding             as TE
import qualified Data.Text.Lazy                 as LT
import           Prelude.Compat
import           Text.RE.REOptions
import           Text.RE.ZeInternals.Types.Capture
import           Text.RE.ZeInternals.Types.CaptureID
import           Text.RE.ZeInternals.Types.Match
import           Text.RE.ZeInternals.Types.Matches
import           Text.Read
import           Text.Regex.TDFA
import           Text.Regex.TDFA.Text()
import           Text.Regex.TDFA.Text.Lazy()
\end{code}


ReContext and RELocation
------------------------

\begin{code}
-- | @REContext@ specifies which contexts the substitutions should be applied
data REContext
  = TOP   -- ^ substitutions should be applied to the top-level only,
          -- the text that matched the whole RE
  | SUB   -- ^ substitutions should only be applied to the text
          -- captured by bracketed sub-REs
  | ALL   -- ^ the substitution function should be applied to all
          -- captures, the top level and the sub-expression captures
  deriving (Show)

-- | the @RELocation@ information passed into the substitution function
-- specifies which sub-expression is being substituted
data RELocation =
  RELocation
    { locationMatch   :: Int
          -- ^ the zero-based, i-th string to be matched,
          -- when matching all strings, zero when only the
          -- first string is being matched
    , locationCapture :: CaptureOrdinal
          -- ^ 0, when matching the top-level string
          -- matched by the whole RE, 1 for the top-most,
          -- left-most redex captured by bracketed
          -- sub-REs, etc.
    }
  deriving (Show)
\end{code}

\begin{code}
-- | True iff the location references a complete match
-- (i.e., not a bracketed capture)
isTopLocation :: RELocation -> Bool
isTopLocation = (==0) . locationCapture
\end{code}

\begin{code}
-- | replace all with a template, $0 for whole text, $1 for first
-- capture, etc.
replaceAll :: Replace a
           => a
           -> Matches a
           -> a
replaceAll tpl ac = replaceAllCaptures TOP (parseTemplateR tpl) ac
\end{code}

\begin{code}
-- | substitutes using a function that takes the full Match
-- context and returns the same replacement text as the _phi_phi
-- context.
replaceAllCaptures :: Replace a
                   => REContext
                   -> (Match a->RELocation->Capture a->Maybe a)
                   -> Matches a
                   -> a
\end{code}

\begin{code}
replaceAllCaptures = replaceAllCaptures_ replaceMethods
\end{code}

\begin{code}
-- | replaceAllCaptures_ is like like replaceAllCaptures but takes the
-- Replace methods through the ReplaceMethods argument
replaceAllCaptures_ :: Extract a
                    => ReplaceMethods a
                    -> REContext
                    -> (Match a->RELocation->Capture a->Maybe a)
                    -> Matches a
                    -> a
replaceAllCaptures_ s ctx phi ac =
    runIdentity $ replaceAllCapturesM s ctx (lift_phi phi) ac
\end{code}

\begin{code}
-- | replaceAllCapturesM is just a monadically generalised version of
-- replaceAllCaptures_
replaceAllCapturesM :: (Extract a,Monad m)
                    => ReplaceMethods a
                    -> REContext
                    -> (Match a->RELocation->Capture a->m (Maybe a))
                    -> Matches a
                    -> m a
replaceAllCapturesM r ctx phi_ Matches{..} =
    replaceCapturesM r ALL phi $ Match matchesSource cnms arr
  where
    phi _ (RELocation _ i) = case arr_c!i of
      Just caps -> phi_ caps . uncurry RELocation $ arr_i ! i
      Nothing   -> const $ return Nothing

    arr_c = listArray bds $
      concat $
        [ repl (rangeSize $ bounds $ matchArray cs) cs
            | cs <- allMatches
            ]

    arr_i = listArray bds j_ks

    arr   = listArray bds $
        [ arr_ ! k
            | arr_ <- map matchArray allMatches
            , k    <- indices arr_
            ]

    bds   = (0,CaptureOrdinal $ length j_ks-1)

    j_ks  =
        [ (j,k)
            | (j,arr_) <- zip [0..] $ map matchArray allMatches
            ,  k       <- indices arr_
            ]

    repl 0 _ = []
    repl n x = case ctx of
      TOP -> Just x  : replicate (n-1) Nothing
      SUB -> Nothing : replicate (n-1) (Just x)
      ALL -> replicate n $ Just x

    cnms = fromMaybe noCaptureNames $ listToMaybe $ map captureNames allMatches
\end{code}

\begin{code}
-- | replace with a template containing $0 for whole text,
-- $1 for first capture, etc.
replace :: Replace a
        => a
        -> Match a
        -> a
replace tpl c = replaceCaptures TOP (parseTemplateR tpl) c
\end{code}

\begin{code}
-- | substitutes using a function that takes the full Match
-- context and returns the same replacement text as the _phi_phi
-- context.
replaceCaptures :: Replace a
                 => REContext
                 -> (Match a->RELocation->Capture a->Maybe a)
                 -> Match a
                 -> a
replaceCaptures = replaceCaptures_ replaceMethods
\end{code}

\begin{code}
-- | replaceCaptures_ is like replaceCaptures but takes the Replace methods
-- through the ReplaceMethods argument
replaceCaptures_ :: Extract a
                 => ReplaceMethods a
                 -> REContext
                 -> (Match a->RELocation->Capture a->Maybe a)
                 -> Match a
                 -> a
replaceCaptures_ s ctx phi caps =
  runIdentity $ replaceCapturesM s ctx (lift_phi phi) caps
\end{code}

\begin{code}
-- | replaceCapturesM is just a monadically generalised version of
-- replaceCaptures_
replaceCapturesM :: (Monad m,Extract a)
                 => ReplaceMethods a
                 -> REContext
                 -> (Match a->RELocation->Capture a->m (Maybe a))
                 -> Match a
                 -> m a
replaceCapturesM ReplaceMethods{..} ctx phi_ caps@Match{..} = do
    (hay',_) <- foldr sc (return (matchSource,[])) $
                    zip [0..] $ elems matchArray
    return hay'
  where
    sc (i,cap0) act = do
      (hay,ds) <- act
      let ndl  = capturedText cap
          cap  = adj hay ds cap0
      mb <- phi i cap
      case mb of
        Nothing   -> return (hay,ds)
        Just ndl' ->
            return
              ( methodSubst (const ndl') cap
              , (captureOffset cap,len'-len) : ds
              )
          where
            len' = methodLength ndl'
            len  = methodLength ndl

    adj hay ds cap =
      Capture
        { captureSource = hay
        , capturedText  = before len $ after off0 hay
        , captureOffset = off0
        , captureLength = len
        }
      where
        len  = len0 + sum
          [ delta
            | (off,delta) <- ds
            , off < off0 + len0
            ]
        len0 = captureLength cap
        off0 = captureOffset cap

    phi i cap = case ctx of
      TOP | i/=0 -> return Nothing
      SUB | i==0 ->return  Nothing
      _          ->
        case not $ hasCaptured cap of
          True  -> return Nothing
          False -> phi_ caps (RELocation 0 i) cap
\end{code}

expandMacros
------------

\begin{code}
-- | expand all of the @{..} macros in the RE in the argument String
-- according to the Macros argument, preprocessing the RE String
-- according to the Mode argument (used internally)
expandMacros :: (r->String) -> Macros r -> String -> String
expandMacros x_src hm s =
  case HM.null hm of
    True  -> s
    False -> expandMacros' (fmap x_src . flip HM.lookup hm) s
\end{code}

\begin{code}
-- | expand the @{..} macros in the argument string using the given
-- function
expandMacros' :: (MacroID->Maybe String) -> String -> String
expandMacros' lu = fixpoint e_m
  where
    e_m re_s = replaceAllCaptures TOP phi $ re_s $=~ "@(@|\\{([^{}]+)\\})"
      where
        phi mtch _ cap = case txt == "@@" of
            True  -> Just   "@"
            False -> Just $ fromMaybe txt $ lu ide
          where
            txt = capturedText cap
            ide = MacroID $ capturedText $ capture c2 mtch
            c2  = IsCaptureOrdinal $ CaptureOrdinal 2
\end{code}

\begin{code}
lift_phi :: Monad m
         => (Match a->RELocation->Capture a->Maybe a)
         -> (Match a->RELocation->Capture a->m (Maybe a))
lift_phi phi_ = phi
  where
    phi caps' loc' cap' = return $ phi_ caps' loc' cap'
\end{code}


templateCaptures
----------------

\begin{code}
-- | list all of the CaptureID references in the replace template in
-- the second argument
templateCaptures :: ( Replace a
                    , RegexContext Regex a (Matches a)
                    , RegexMaker   Regex CompOption ExecOption String
                    )
                 => (a->String)
                 -> a
                 -> [CaptureID]
templateCaptures unpack tpl =
    [ cid
      | mtch <- allMatches $ scan_template tpl
      , Right cid <- [parse_template_capture unpack mtch]
      ]

-- | parse a Match generated by acan_template, returning @Left "$")
-- iff the capture reference is an escaped @$@ (i.e., @$$@)
parse_template_capture :: (a->String) -> Match a -> Either a CaptureID
parse_template_capture unpack t_mtch = case t_mtch !$? c2 of
  Just cap -> case readMaybe stg of
      Nothing -> Right $ IsCaptureName    $ CaptureName $ T.pack stg
      Just cn -> Right $ IsCaptureOrdinal $ CaptureOrdinal cn
    where
      stg = unpack $ capturedText cap
  Nothing -> case s == "$" of
    True  -> Left t
    False -> Right $ IsCaptureOrdinal $ CaptureOrdinal $ read s
  where
    s = unpack t
    t = capturedText $ capture c1 t_mtch

    c1 = IsCaptureOrdinal $ CaptureOrdinal 1
    c2 = IsCaptureOrdinal $ CaptureOrdinal 2

-- | scan a replacement template, returning a Match for each capture
-- reference in the template (like $1, ${foo})
scan_template :: ( Replace a
                 , RegexContext Regex a (Matches a)
                 , RegexMaker   Regex CompOption ExecOption String
                 )
              => a
              -> Matches a
scan_template tpl = tpl $=~ "\\$(\\$|[0-9]|\\{([^{}]+)\\})"
\end{code}


Replace and ReplaceMethods
--------------------------

\begin{code}
-- | Replace provides the missing needed to replace the matched
-- text in a @Replace a => Match a@.
class (Show a,Eq a,Ord a,Extract a,Monoid a) => Replace a where
  -- | length function for a
  lengthR        :: a -> Int
  -- | inject String into a
  packR          :: String -> a
  -- | project a onto a String
  unpackR        :: a -> String
  -- | inject into Text
  textifyR       :: a -> T.Text
  -- | project Text onto a
  detextifyR     :: T.Text -> a
  -- | split into lines
  linesR         :: a -> [a]
  -- | concatenate a list of lines
  unlinesR       :: [a] -> a
  -- | append a newline
  appendNewlineR :: a -> a
  -- | apply a substitution function to a Capture
  substR         :: (a->a) -> Capture a -> a
  -- | convert a template containing $0, $1, etc., in the first
  -- argument, into a 'phi' replacement function for use with
  -- replaceAllCaptures and replaceCaptures
  parseTemplateR :: a -> Match a -> RELocation -> Capture a -> Maybe a

  textifyR       = T.pack . unpackR
  detextifyR     = packR  . T.unpack
  appendNewlineR = (M.<> packR "\n")

  substR f m@Capture{..} =
    capturePrefix m M.<> f capturedText M.<> captureSuffix m
\end{code}

\begin{code}
-- | a selection of the Replace methods can be encapsulated with ReplaceMethods
-- for the higher-order replacement functions
data ReplaceMethods a =
  ReplaceMethods
    { methodLength :: a -> Int
    , methodSubst  :: (a->a) -> Capture a -> a
    }

-- | replaceMethods encapsulates ReplaceMethods a from a Replace a context
replaceMethods :: Replace a => ReplaceMethods a
replaceMethods =
  ReplaceMethods
    { methodLength = lengthR
    , methodSubst  = substR
    }
\end{code}


The Replace Instances
---------------------

\begin{code}
instance Replace [Char] where
  lengthR         = length
  packR           = id
  unpackR         = id
  textifyR        = T.pack
  detextifyR      = T.unpack
  linesR          = lines
  unlinesR        = unlines
  appendNewlineR  = (M.<>"\n")
  parseTemplateR  = parseTemplateR' id

instance Replace B.ByteString where
  lengthR         = B.length
  packR           = B.pack
  unpackR         = B.unpack
  textifyR        = TE.decodeUtf8
  detextifyR      = TE.encodeUtf8
  linesR          = B.lines
  unlinesR        = B.unlines
  appendNewlineR  = (M.<>"\n")
  parseTemplateR  = parseTemplateR' B.unpack

instance Replace LBS.ByteString where
  lengthR         = fromEnum . LBS.length
  packR           = LBS.pack
  unpackR         = LBS.unpack
  textifyR        = TE.decodeUtf8  . LBS.toStrict
  linesR          = LBS.lines
  unlinesR        = LBS.unlines
  detextifyR      = LBS.fromStrict . TE.encodeUtf8
  appendNewlineR  = (M.<>"\n")
  parseTemplateR  = parseTemplateR' LBS.unpack

instance Replace (S.Seq Char) where
  lengthR         = S.length
  packR           = S.fromList
  unpackR         = F.toList
  linesR          = map packR . lines . unpackR
  unlinesR        = packR . unlines . map unpackR
  parseTemplateR  = parseTemplateR' F.toList

instance Replace T.Text where
  lengthR         = T.length
  packR           = T.pack
  unpackR         = T.unpack
  textifyR        = id
  detextifyR      = id
  linesR          = T.lines
  unlinesR        = T.unlines
  appendNewlineR  = (M.<>"\n")
  parseTemplateR  = parseTemplateR' T.unpack

instance Replace LT.Text where
  lengthR         = fromEnum . LT.length
  packR           = LT.pack
  unpackR         = LT.unpack
  textifyR        = LT.toStrict
  detextifyR      = LT.fromStrict
  linesR          = LT.lines
  unlinesR        = LT.unlines
  appendNewlineR  = (M.<>"\n")
  parseTemplateR  = parseTemplateR' LT.unpack
\end{code}


Parsing Replace Templates
-------------------------

\begin{code}
-- | parse the replacement template in second argument, substituting
-- the capture references with corresponding captures from the Match
-- in the third argument (the result of a single match of the RE
-- against the input text to be matched); Nothing is returned if the
-- inputs are not well formed (currently all inputs are well formed)
parseTemplateR' :: ( Replace a
                   , RegexContext Regex a (Matches a)
                   , RegexMaker   Regex CompOption ExecOption String
                   )
                   => (a->String)
                   -> a
                   -> Match a
                   -> RELocation
                   -> Capture a
                   -> Maybe a
parseTemplateR' unpack tpl mtch _ _ =
    Just $ replaceAllCaptures TOP phi $ scan_template tpl
  where
    phi t_mtch _ _ = either Just this $ parse_template_capture unpack t_mtch

    this cid       = capturedText <$> mtch !$? cid
\end{code}


Helpers
-------

\begin{code}
fixpoint :: (Eq a) => (a->a) -> a -> a
fixpoint f = chk . iterate f
  where
    chk (x:x':_) | x==x' = x
    chk xs               = chk $ tail xs
\end{code}

\begin{code}
($=~) :: ( RegexContext Regex source target
         , RegexMaker   Regex CompOption ExecOption String
         )
      => source -> String -> target
($=~) = (=~)
\end{code}