File: Matches.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 (83 lines) | stat: -rw-r--r-- 2,288 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
\begin{code}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE UndecidableInstances       #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE MonoLocalBinds             #-}
\end{code}

\begin{code}
module Text.RE.ZeInternals.Types.Matches
  ( Matches(..)
  , anyMatches
  , countMatches
  , matches
  , mainCaptures
  ) where
\end{code}

\begin{code}
import           Data.Typeable
import           Text.RE.ZeInternals.Types.Capture
import           Text.RE.ZeInternals.Types.CaptureID
import           Text.RE.ZeInternals.Types.Match
import           Text.Regex.Base
\end{code}


\begin{code}
-- | the result of matching a RE against a text (with @*=~@), retaining
-- the text that was matched against
data Matches a =
  Matches
    { matchesSource :: !a          -- ^ the source text being matched
    , allMatches    :: ![Match a]  -- ^ all 'Match' instances found, left to right
    }
  deriving (Show,Eq,Typeable)
\end{code}

\begin{code}
instance Functor Matches where
  fmap f Matches{..} =
    Matches
      { matchesSource = f matchesSource
      , allMatches    = map (fmap f) allMatches
      }
\end{code}

\begin{code}
-- | tests whether the RE matched the source text at all
anyMatches :: Matches a -> Bool
anyMatches = not . null . allMatches

-- | count the matches
countMatches :: Matches a -> Int
countMatches = length . allMatches

-- | list the texts that Matched
matches :: Matches a -> [a]
matches = map capturedText . mainCaptures

-- | extract the main capture from each match
mainCaptures :: Matches a -> [Capture a]
mainCaptures ac = [ capture c0 cs | cs<-allMatches ac ]
  where
    c0 = IsCaptureOrdinal $ CaptureOrdinal 0
\end{code}

\begin{code}
-- | this instance hooks 'Matches' into regex-base: regex consumers need
-- not worry about any of this
instance
    ( RegexContext regex source [MatchText source]
    , RegexLike    regex source
    , RegexFix     regex source
    ) =>
  RegexContext regex source (Matches source) where
    match  r s = Matches s $ map (convertMatchText r s) $ match r s
    matchM r s = do
      y <- matchM r s
      return $ Matches s $ map (convertMatchText r s) y
\end{code}