File: REOptions.lhs

package info (click to toggle)
haskell-regex 1.1.0.2-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 424 kB
  • sloc: haskell: 4,533; makefile: 3
file content (111 lines) | stat: -rw-r--r-- 3,396 bytes parent folder | download
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
\begin{code}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE FunctionalDependencies     #-}
{-# LANGUAGE CPP                        #-}
#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE TemplateHaskellQuotes      #-}
{-# LANGUAGE DeriveLift                 #-}
{-# LANGUAGE StandaloneDeriving         #-}
#else
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE TemplateHaskell            #-}
#endif

module Text.RE.REOptions
  (
  -- * The Options Tutorial
  -- $tutorial

  -- * 'SimpleREOptions'
    SimpleREOptions(..)
  -- * 'REOptions_'
  , REOptions_(..)
  -- * The Macro Tables
  , Macros
  , MacroID(..)
  , emptyMacros
  ) where

import qualified Data.HashMap.Strict        as HM
import           Data.Hashable
import           Data.String
import           Language.Haskell.TH.Syntax
\end{code}


The RE Options
--------------

\begin{code}
-- | the default API uses these simple, universal RE options,
-- which get auto-converted into the appropriate back-end 'REOptions_'
data SimpleREOptions
  = MultilineSensitive        -- ^ case-sensitive with ^ and $ matching the start and end of a line
  | MultilineInsensitive      -- ^ case-insensitive with ^ and $ matsh the start and end of a line
  | BlockSensitive            -- ^ case-sensitive with ^ and $ matching the start and end of the input text
  | BlockInsensitive          -- ^ case-insensitive with ^ and $ matching the start and end of the input text
  deriving (Bounded,Enum,Eq,Ord,Show)
\end{code}

\begin{code}
-- | we need to use this in the quasi quoters to specify @SimpleREOptions@
-- selected by the quasi quoter
deriving instance Lift SimpleREOptions
\end{code}

\begin{code}
-- | the general options for an RE are dependent on which back end is
-- being used and are parameterised over the @RE@ type for the back end,
-- and its @CompOption@ and @ExecOption@ types (the compile-time and
-- execution time options, respectively); each back end will define an
-- @REOptions@ type that fills out these three type parameters with the
-- appropriate types (see, for example, "Text.RE.TDFA")
data REOptions_ r c e =
  REOptions
    { optionsMacs :: !(Macros r)    -- ^ the available TestBench RE macros
    , optionsComp :: !c             -- ^ the back end compile-time options
    , optionsExec :: !e             -- ^ the back end execution-time options
    }
  deriving (Show)
\end{code}


The Macro Tables
----------------

\begin{code}
-- | our macro tables are parameterised over the back end @RE@ type and
-- and just associate each @MacroID@ with an @RE@ (which may in turn
-- contain macros to be expanded)
type Macros r = HM.HashMap MacroID r
\end{code}

\begin{code}
-- | @MacroID@ is just a wrapped @String@ type with an @IsString@
-- instance
newtype MacroID =
    MacroID { getMacroID :: String }
  deriving (IsString,Ord,Eq,Show)
\end{code}

\begin{code}
-- | @MacroID@ is used with @HM.HashMap@ to build macro lookup tables
instance Hashable MacroID where
  hashWithSalt i = hashWithSalt i . getMacroID
\end{code}

\begin{code}
-- | a macro table containing no entries
emptyMacros :: Macros r
emptyMacros = HM.empty
\end{code}


\begin{code}
-- $tutorial
-- This API module provides the generic types used to specify the options
-- when compiling REs for each of the backl ends.
--
-- See the tutorials at http://re-tutorial-options.regex.uk
\end{code}