a8a51c066c7daa6c60b29818ff55da3e91789f6f
[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   , ReadS
51   , readP_to_S
52   , readS_to_P
53   )
54
55 import qualified Text.ParserCombinators.ReadP as ReadP
56   ( get
57   , look
58   , (+++), (<++)
59   , pfail
60   )
61
62 import Control.Monad( MonadPlus(..) )
63 #ifdef __GLASGOW_HASKELL__
64 import GHC.Num( Num(..) )
65 import GHC.Base
66 #endif
67
68 -- ---------------------------------------------------------------------------
69 -- The readPrec type
70
71 newtype ReadPrec a = P { unP :: Prec -> ReadP a }
72
73 -- Functor, Monad, MonadPlus
74
75 instance Functor ReadPrec where
76   fmap h (P f) = P (\n -> fmap h (f n))
77
78 instance Monad ReadPrec where
79   return x  = P (\_ -> return x)
80   fail s    = P (\_ -> fail s)
81   P f >>= k = P (\n -> do a <- f n; let P f' = k a in f' n)
82   
83 instance MonadPlus ReadPrec where
84   mzero = pfail
85   mplus = (+++)
86
87 -- precedences
88   
89 type Prec = Int
90
91 minPrec :: Prec
92 minPrec = 0
93
94 -- ---------------------------------------------------------------------------
95 -- Operations over ReadPrec
96
97 lift :: ReadP a -> ReadPrec a
98 -- ^ Lift a precedence-insensitive 'ReadP' to a 'ReadPrec'
99 lift m = P (\_ -> m)
100
101 step :: ReadPrec a -> ReadPrec a
102 -- ^ Increases the precedence context by one
103 step (P f) = P (\n -> f (n+1))
104
105 reset :: ReadPrec a -> ReadPrec a
106 -- ^ Resets the precedence context to zero
107 reset (P f) = P (\n -> f minPrec)
108
109 prec :: Prec -> ReadPrec a -> ReadPrec a
110 -- ^ @(prec n p)@ checks that the precedence context is 
111 --                        less than or equal to n,
112 --   * if not, fails
113 --   * if so, parses p in context n
114 prec n (P f) = P (\c -> if c <= n then f n else ReadP.pfail)
115
116 -- ---------------------------------------------------------------------------
117 -- Derived operations
118
119 get :: ReadPrec Char
120 get = lift ReadP.get
121
122 look :: ReadPrec String
123 look = lift ReadP.look
124
125 (+++) :: ReadPrec a -> ReadPrec a -> ReadPrec a
126 P f1 +++ P f2 = P (\n -> f1 n ReadP.+++ f2 n)
127
128 (<++) :: ReadPrec a -> ReadPrec a -> ReadPrec a
129 P f1 <++ P f2 = P (\n -> f1 n ReadP.<++ f2 n)
130
131 pfail :: ReadPrec a
132 pfail = lift ReadP.pfail
133
134 choice :: [ReadPrec a] -> ReadPrec a
135 choice ps = foldr (+++) pfail ps
136
137 -- ---------------------------------------------------------------------------
138 -- Converting between ReadPrec and Read
139
140 readPrec_to_P :: ReadPrec a -> (Int -> ReadP a)
141 readPrec_to_P (P f) = f
142
143 readP_to_Prec :: (Int -> ReadP a) -> ReadPrec a
144 readP_to_Prec f = P f
145
146 readPrec_to_S :: ReadPrec a -> (Int -> ReadS a)
147 readPrec_to_S (P f) n = readP_to_S (f n)
148
149 readS_to_Prec :: (Int -> ReadS a) -> ReadPrec a
150 readS_to_Prec f = P (\n -> readS_to_P (f n))