[project @ 2003-08-19 16:39:13 by simonmar]
[ghc-base.git] / Text / Read / Lex.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Text.Read.Lex
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 -- The cut-down Haskell lexer, used by Text.Read
13 --
14 -----------------------------------------------------------------------------
15
16 module Text.Read.Lex
17   -- lexing types
18   ( Lexeme(..)  -- :: *; Show, Eq
19                 
20   -- lexer      
21   , lex         -- :: ReadP Lexeme      Skips leading spaces
22   , hsLex       -- :: ReadP String
23   , lexChar     -- :: ReadP Char        Reads just one char, with H98 escapes
24   
25   , readIntP    -- :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadP a
26   , readOctP    -- :: Num a => ReadP a 
27   , readDecP    -- :: Num a => ReadP a
28   , readHexP    -- :: Num a => ReadP a
29   )
30  where
31
32 import Text.ParserCombinators.ReadP
33
34 #ifdef __GLASGOW_HASKELL__
35 import GHC.Base
36 import GHC.Num( Num(..), Integer )
37 import GHC.Show( Show(..) )
38 import {-# SOURCE #-} GHC.Unicode ( isSpace, isAlpha, isAlphaNum )
39 import GHC.Real( Ratio(..), Integral, Rational, (%), fromIntegral, 
40                  toInteger, (^), (^^), infinity, notANumber )
41 import GHC.List
42 import GHC.Enum( maxBound )
43 #else
44 import Prelude hiding ( lex )
45 import Data.Char( chr, ord, isSpace, isAlpha, isAlphaNum )
46 import Data.Ratio( Ratio, (%) )
47 #endif
48 #ifdef __HUGS__
49 import Hugs.Prelude( Ratio(..) )
50 #endif
51 import Data.Maybe
52 import Control.Monad
53
54 -- -----------------------------------------------------------------------------
55 -- Lexing types
56
57 data Lexeme
58   = Char   Char         -- Quotes removed, 
59   | String String       --      escapes interpreted
60   | Punc   String       -- Punctuation, eg "(", "::"
61   | Ident  String       -- Haskell identifiers, e.g. foo, baz
62   | Symbol String       -- Haskell symbols, e.g. >>, %
63   | Int Integer
64   | Rat Rational
65   | EOF
66  deriving (Eq, Show)
67
68 -- -----------------------------------------------------------------------------
69 -- Lexing
70
71 lex :: ReadP Lexeme
72 lex = skipSpaces >> lexToken
73
74 hsLex :: ReadP String
75 -- ^ Haskell lexer: returns the lexed string, rather than the lexeme
76 hsLex = do skipSpaces 
77            (s,_) <- gather lexToken
78            return s
79
80 lexToken :: ReadP Lexeme
81 lexToken = lexEOF     +++
82            lexLitChar +++ 
83            lexString  +++ 
84            lexPunc    +++ 
85            lexSymbol  +++ 
86            lexId      +++ 
87            lexNumber
88
89
90 -- ----------------------------------------------------------------------
91 -- End of file
92 lexEOF :: ReadP Lexeme
93 lexEOF = do s <- look
94             guard (null s)
95             return EOF
96
97 -- ---------------------------------------------------------------------------
98 -- Single character lexemes
99
100 lexPunc :: ReadP Lexeme
101 lexPunc =
102   do c <- satisfy isPuncChar
103      return (Punc [c])
104  where
105   isPuncChar c = c `elem` ",;()[]{}`"
106
107 -- ----------------------------------------------------------------------
108 -- Symbols
109
110 lexSymbol :: ReadP Lexeme
111 lexSymbol =
112   do s <- munch1 isSymbolChar
113      if s `elem` reserved_ops then 
114         return (Punc s)         -- Reserved-ops count as punctuation
115       else
116         return (Symbol s)
117  where
118   isSymbolChar c = c `elem` "!@#$%&*+./<=>?\\^|:-~"
119   reserved_ops   = ["..", "::", "=", "\\", "|", "<-", "->", "@", "~", "=>"]
120
121 -- ----------------------------------------------------------------------
122 -- identifiers
123
124 lexId :: ReadP Lexeme
125 lexId = lex_nan <++ lex_id
126   where
127         -- NaN and Infinity look like identifiers, so
128         -- we parse them first.  
129     lex_nan = (string "NaN"      >> return (Rat notANumber)) +++
130               (string "Infinity" >> return (Rat infinity))
131   
132     lex_id = do c <- satisfy isIdsChar
133                 s <- munch isIdfChar
134                 return (Ident (c:s))
135
136           -- Identifiers can start with a '_'
137     isIdsChar c = isAlpha c || c == '_'
138     isIdfChar c = isAlphaNum c || c `elem` "_'"
139
140 #ifndef __GLASGOW_HASKELL__
141 infinity, notANumber :: Rational
142 infinity   = 1 :% 0
143 notANumber = 0 :% 0
144 #endif
145
146 -- ---------------------------------------------------------------------------
147 -- Lexing character literals
148
149 lexLitChar :: ReadP Lexeme
150 lexLitChar =
151   do char '\''
152      (c,esc) <- lexCharE
153      guard (esc || c /= '\'')   -- Eliminate '' possibility
154      char '\''
155      return (Char c)
156
157 lexChar :: ReadP Char
158 lexChar = do { (c,_) <- lexCharE; return c }
159
160 lexCharE :: ReadP (Char, Bool)  -- "escaped or not"?
161 lexCharE =
162   do c <- get
163      if c == '\\'
164        then do c <- lexEsc; return (c, True)
165        else do return (c, False)
166  where 
167   lexEsc =
168     lexEscChar
169       +++ lexNumeric
170         +++ lexCntrlChar
171           +++ lexAscii
172   
173   lexEscChar =
174     do c <- get
175        case c of
176          'a'  -> return '\a'
177          'b'  -> return '\b'
178          'f'  -> return '\f'
179          'n'  -> return '\n'
180          'r'  -> return '\r'
181          't'  -> return '\t'
182          'v'  -> return '\v'
183          '\\' -> return '\\'
184          '\"' -> return '\"'
185          '\'' -> return '\''
186          _    -> pfail
187   
188   lexNumeric =
189     do base <- lexBaseChar
190        n    <- lexInteger base
191        guard (n <= toInteger (ord maxBound))
192        return (chr (fromInteger n))
193
194   lexCntrlChar =
195     do char '^'
196        c <- get
197        case c of
198          '@'  -> return '\^@'
199          'A'  -> return '\^A'
200          'B'  -> return '\^B'
201          'C'  -> return '\^C'
202          'D'  -> return '\^D'
203          'E'  -> return '\^E'
204          'F'  -> return '\^F'
205          'G'  -> return '\^G'
206          'H'  -> return '\^H'
207          'I'  -> return '\^I'
208          'J'  -> return '\^J'
209          'K'  -> return '\^K'
210          'L'  -> return '\^L'
211          'M'  -> return '\^M'
212          'N'  -> return '\^N'
213          'O'  -> return '\^O'
214          'P'  -> return '\^P'
215          'Q'  -> return '\^Q'
216          'R'  -> return '\^R'
217          'S'  -> return '\^S'
218          'T'  -> return '\^T'
219          'U'  -> return '\^U'
220          'V'  -> return '\^V'
221          'W'  -> return '\^W'
222          'X'  -> return '\^X'
223          'Y'  -> return '\^Y'
224          'Z'  -> return '\^Z'
225          '['  -> return '\^['
226          '\\' -> return '\^\'
227          ']'  -> return '\^]'
228          '^'  -> return '\^^'
229          '_'  -> return '\^_'
230          _    -> pfail
231
232   lexAscii =
233     do choice
234          [ (string "SOH" >> return '\SOH') <++
235            (string "SO"  >> return '\SO') 
236                 -- \SO and \SOH need maximal-munch treatment
237                 -- See the Haskell report Sect 2.6
238
239          , string "NUL" >> return '\NUL'
240          , string "STX" >> return '\STX'
241          , string "ETX" >> return '\ETX'
242          , string "EOT" >> return '\EOT'
243          , string "ENQ" >> return '\ENQ'
244          , string "ACK" >> return '\ACK'
245          , string "BEL" >> return '\BEL'
246          , string "BS"  >> return '\BS'
247          , string "HT"  >> return '\HT'
248          , string "LF"  >> return '\LF'
249          , string "VT"  >> return '\VT'
250          , string "FF"  >> return '\FF'
251          , string "CR"  >> return '\CR'
252          , string "SI"  >> return '\SI'
253          , string "DLE" >> return '\DLE'
254          , string "DC1" >> return '\DC1'
255          , string "DC2" >> return '\DC2'
256          , string "DC3" >> return '\DC3'
257          , string "DC4" >> return '\DC4'
258          , string "NAK" >> return '\NAK'
259          , string "SYN" >> return '\SYN'
260          , string "ETB" >> return '\ETB'
261          , string "CAN" >> return '\CAN'
262          , string "EM"  >> return '\EM'
263          , string "SUB" >> return '\SUB'
264          , string "ESC" >> return '\ESC'
265          , string "FS"  >> return '\FS'
266          , string "GS"  >> return '\GS'
267          , string "RS"  >> return '\RS'
268          , string "US"  >> return '\US'
269          , string "SP"  >> return '\SP'
270          , string "DEL" >> return '\DEL'
271          ]
272
273
274 -- ---------------------------------------------------------------------------
275 -- string literal
276
277 lexString :: ReadP Lexeme
278 lexString =
279   do char '"'
280      body id
281  where
282   body f =
283     do (c,esc) <- lexStrItem
284        if c /= '"' || esc
285          then body (f.(c:))
286          else let s = f "" in
287               return (String s)
288
289   lexStrItem = (lexEmpty >> lexStrItem)
290                +++ lexCharE
291   
292   lexEmpty =
293     do char '\\'
294        c <- get
295        case c of
296          '&'           -> do return ()
297          _ | isSpace c -> do skipSpaces; char '\\'; return ()
298          _             -> do pfail
299
300 -- ---------------------------------------------------------------------------
301 --  Lexing numbers
302
303 type Base   = Int
304 type Digits = [Int]
305
306 lexNumber :: ReadP Lexeme
307 lexNumber 
308   = lexHexOct  <++      -- First try for hex or octal 0x, 0o etc
309                         -- If that fails, try for a decimal number
310     lexDecNumber        -- Start with ordinary digits
311                 
312 lexHexOct :: ReadP Lexeme
313 lexHexOct
314   = do  char '0'
315         base <- lexBaseChar
316         digits <- lexDigits base
317         return (Int (val (fromIntegral base) 0 digits))
318
319 lexBaseChar :: ReadP Int
320 -- Lex a single character indicating the base, 
321 -- or return 10 if there isn't one
322 lexBaseChar = lex_base <++ return 10
323    where
324       lex_base = do { c <- get;
325                       case c of
326                         'o' -> return 8
327                         'O' -> return 8
328                         'x' -> return 16
329                         'X' -> return 16
330                         _   -> pfail } 
331
332 lexDecNumber :: ReadP Lexeme
333 lexDecNumber =
334   do xs    <- lexDigits 10
335      mFrac <- lexFrac <++ return Nothing
336      mExp  <- lexExp  <++ return Nothing
337      return (value xs mFrac mExp)
338  where
339   value xs mFrac mExp = valueFracExp (val 10 0 xs) mFrac mExp
340   
341   valueFracExp :: Integer -> Maybe Digits -> Maybe Integer 
342                -> Lexeme
343   valueFracExp a Nothing Nothing        
344     = Int a                                             -- 43
345   valueFracExp a Nothing (Just exp)
346     | exp >= 0  = Int (a * (10 ^ exp))                  -- 43e7
347     | otherwise = Rat (valExp (fromInteger a) exp)      -- 43e-7
348   valueFracExp a (Just fs) mExp 
349      = case mExp of
350          Nothing  -> Rat rat                            -- 4.3
351          Just exp -> Rat (valExp rat exp)               -- 4.3e-4
352      where
353         rat :: Rational
354         rat = fromInteger a + frac 10 0 1 fs
355
356   valExp :: Rational -> Integer -> Rational
357   valExp rat exp = rat * (10 ^^ exp)
358
359 lexFrac :: ReadP (Maybe Digits)
360 -- Read the fractional part; fail if it doesn't
361 -- start ".d" where d is a digit
362 lexFrac = do char '.'
363              frac <- lexDigits 10
364              return (Just frac)
365
366 lexExp :: ReadP (Maybe Integer)
367 lexExp = do char 'e' +++ char 'E'
368             exp <- signedExp +++ lexInteger 10
369             return (Just exp)
370  where
371    signedExp 
372      = do c <- char '-' +++ char '+'
373           n <- lexInteger 10
374           return (if c == '-' then -n else n)
375
376 lexDigits :: Int -> ReadP Digits
377 -- Lex a non-empty sequence of digits in specified base
378 lexDigits base =
379   do s  <- look
380      xs <- scan s id
381      guard (not (null xs))
382      return xs
383  where
384   scan (c:cs) f = case valDig base c of
385                     Just n  -> do get; scan cs (f.(n:))
386                     Nothing -> do return (f [])
387   scan []     f = do return (f [])
388
389 lexInteger :: Base -> ReadP Integer
390 lexInteger base =
391   do xs <- lexDigits base
392      return (val (fromIntegral base) 0 xs)
393
394 val :: Num a => a -> a -> Digits -> a
395 -- val base y [d1,..,dn] = y ++ [d1,..,dn], as it were
396 val base y []     = y
397 val base y (x:xs) = y' `seq` val base y' xs
398  where
399   y' = y * base + fromIntegral x
400
401 frac :: Integral a => a -> a -> a -> Digits -> Ratio a
402 frac base a b []     = a % b
403 frac base a b (x:xs) = a' `seq` b' `seq` frac base a' b' xs
404  where
405   a' = a * base + fromIntegral x
406   b' = b * base
407
408 valDig :: Num a => a -> Char -> Maybe Int
409 valDig 8 c
410   | '0' <= c && c <= '7' = Just (ord c - ord '0')
411   | otherwise            = Nothing
412
413 valDig 10 c = valDecDig c
414
415 valDig 16 c
416   | '0' <= c && c <= '9' = Just (ord c - ord '0')
417   | 'a' <= c && c <= 'f' = Just (ord c - ord 'a' + 10)
418   | 'A' <= c && c <= 'F' = Just (ord c - ord 'A' + 10)
419   | otherwise            = Nothing
420
421 valDecDig c
422   | '0' <= c && c <= '9' = Just (ord c - ord '0')
423   | otherwise            = Nothing
424
425 -- ----------------------------------------------------------------------
426 -- other numeric lexing functions
427
428 readIntP :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadP a
429 readIntP base isDigit valDigit =
430   do s <- munch1 isDigit
431      return (val base 0 (map valDigit s))
432
433 readIntP' :: Num a => a -> ReadP a
434 readIntP' base = readIntP base isDigit valDigit
435  where
436   isDigit  c = maybe False (const True) (valDig base c)
437   valDigit c = maybe 0     id           (valDig base c)
438
439 readOctP, readDecP, readHexP :: Num a => ReadP a
440 readOctP = readIntP' 8
441 readDecP = readIntP' 10
442 readHexP = readIntP' 16