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