Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Text / ParserCombinators / ReadPrec.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Text.ParserCombinators.ReadPrec
6 -- Copyright   :  (c) The University of Glasgow 2002
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  non-portable (uses Text.ParserCombinators.ReadP)
12 --
13 -- This library defines parser combinators for precedence parsing.
14
15 -----------------------------------------------------------------------------
16
17 module Text.ParserCombinators.ReadPrec
18   ( 
19   ReadPrec,      -- :: * -> *; instance Functor, Monad, MonadPlus
20   
21   -- * Precedences
22   Prec,          -- :: *; = Int
23   minPrec,       -- :: Prec; = 0
24
25   -- * Precedence operations
26   lift,          -- :: ReadP a -> ReadPrec a
27   prec,          -- :: Prec -> ReadPrec a -> ReadPrec a
28   step,          -- :: ReadPrec a -> ReadPrec a
29   reset,         -- :: ReadPrec a -> ReadPrec a
30
31   -- * Other operations
32   -- | All are based directly on their similarly-named 'ReadP' counterparts.
33   get,           -- :: ReadPrec Char
34   look,          -- :: ReadPrec String
35   (+++),         -- :: ReadPrec a -> ReadPrec a -> ReadPrec a
36   (<++),         -- :: ReadPrec a -> ReadPrec a -> ReadPrec a
37   pfail,         -- :: ReadPrec a
38   choice,        -- :: [ReadPrec a] -> ReadPrec a
39
40   -- * Converters
41   readPrec_to_P, -- :: ReadPrec a       -> (Int -> ReadP a)
42   readP_to_Prec, -- :: (Int -> ReadP a) -> ReadPrec a
43   readPrec_to_S, -- :: ReadPrec a       -> (Int -> ReadS a)
44   readS_to_Prec, -- :: (Int -> ReadS a) -> ReadPrec a
45   )
46  where
47
48
49 import Text.ParserCombinators.ReadP
50   ( ReadP
51   , ReadS
52   , readP_to_S
53   , readS_to_P
54   )
55
56 import qualified Text.ParserCombinators.ReadP as ReadP
57   ( get
58   , look
59   , (+++), (<++)
60   , pfail
61   )
62
63 import Control.Monad( MonadPlus(..) )
64 #ifdef __GLASGOW_HASKELL__
65 import GHC.Num( Num(..) )
66 import GHC.Base
67 #endif
68
69 -- ---------------------------------------------------------------------------
70 -- The readPrec type
71
72 newtype ReadPrec a = P (Prec -> ReadP a)
73
74 -- Functor, Monad, MonadPlus
75
76 instance Functor ReadPrec where
77   fmap h (P f) = P (\n -> fmap h (f n))
78
79 instance Monad ReadPrec where
80   return x  = P (\_ -> return x)
81   fail s    = P (\_ -> fail s)
82   P f >>= k = P (\n -> do a <- f n; let P f' = k a in f' n)
83   
84 instance MonadPlus ReadPrec where
85   mzero = pfail
86   mplus = (+++)
87
88 -- precedences
89   
90 type Prec = Int
91
92 minPrec :: Prec
93 minPrec = 0
94
95 -- ---------------------------------------------------------------------------
96 -- Operations over ReadPrec
97
98 lift :: ReadP a -> ReadPrec a
99 -- ^ Lift a precedence-insensitive 'ReadP' to a 'ReadPrec'.
100 lift m = P (\_ -> m)
101
102 step :: ReadPrec a -> ReadPrec a
103 -- ^ Increases the precedence context by one.
104 step (P f) = P (\n -> f (n+1))
105
106 reset :: ReadPrec a -> ReadPrec a
107 -- ^ Resets the precedence context to zero.
108 reset (P f) = P (\_ -> f minPrec)
109
110 prec :: Prec -> ReadPrec a -> ReadPrec a
111 -- ^ @(prec n p)@ checks whether the precedence context is 
112 --   less than or equal to @n@, and
113 --
114 --   * if not, fails
115 --
116 --   * if so, parses @p@ in context @n@.
117 prec n (P f) = P (\c -> if c <= n then f n else ReadP.pfail)
118
119 -- ---------------------------------------------------------------------------
120 -- Derived operations
121
122 get :: ReadPrec Char
123 -- ^ Consumes and returns the next character.
124 --   Fails if there is no input left.
125 get = lift ReadP.get
126
127 look :: ReadPrec String
128 -- ^ Look-ahead: returns the part of the input that is left, without
129 --   consuming it.
130 look = lift ReadP.look
131
132 (+++) :: ReadPrec a -> ReadPrec a -> ReadPrec a
133 -- ^ Symmetric choice.
134 P f1 +++ P f2 = P (\n -> f1 n ReadP.+++ f2 n)
135
136 (<++) :: ReadPrec a -> ReadPrec a -> ReadPrec a
137 -- ^ Local, exclusive, left-biased choice: If left parser
138 --   locally produces any result at all, then right parser is
139 --   not used.
140 P f1 <++ P f2 = P (\n -> f1 n ReadP.<++ f2 n)
141
142 pfail :: ReadPrec a
143 -- ^ Always fails.
144 pfail = lift ReadP.pfail
145
146 choice :: [ReadPrec a] -> ReadPrec a
147 -- ^ Combines all parsers in the specified list.
148 choice ps = foldr (+++) pfail ps
149
150 -- ---------------------------------------------------------------------------
151 -- Converting between ReadPrec and Read
152
153 readPrec_to_P :: ReadPrec a -> (Int -> ReadP a)
154 readPrec_to_P (P f) = f
155
156 readP_to_Prec :: (Int -> ReadP a) -> ReadPrec a
157 readP_to_Prec f = P f
158
159 readPrec_to_S :: ReadPrec a -> (Int -> ReadS a)
160 readPrec_to_S (P f) n = readP_to_S (f n)
161
162 readS_to_Prec :: (Int -> ReadS a) -> ReadPrec a
163 readS_to_Prec f = P (\n -> readS_to_P (f n))