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