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