Adjust behaviour of gcd
[ghc-base.git] / Text / Read.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Text.Read
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  non-portable (uses Text.ParserCombinators.ReadP)
12 --
13 -- Converting strings to values.
14 --
15 -- The "Text.Read" library is the canonical library to import for
16 -- 'Read'-class facilities.  For GHC only, it offers an extended and much
17 -- improved 'Read' class, which constitutes a proposed alternative to the 
18 -- Haskell 98 'Read'.  In particular, writing parsers is easier, and
19 -- the parsers are much more efficient.
20 --
21 -----------------------------------------------------------------------------
22
23 module Text.Read (
24    -- * The 'Read' class
25    Read(..),            -- The Read class
26    ReadS,               -- String -> Maybe (a,String)
27
28    -- * Haskell 98 functions
29    reads,               -- :: (Read a) => ReadS a
30    read,                -- :: (Read a) => String -> a
31    readParen,           -- :: Bool -> ReadS a -> ReadS a
32    lex,                 -- :: ReadS String
33
34 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
35    -- * New parsing functions
36    module Text.ParserCombinators.ReadPrec,
37    L.Lexeme(..),
38    lexP,                -- :: ReadPrec Lexeme
39    parens,              -- :: ReadPrec a -> ReadPrec a
40 #endif
41 #ifdef __GLASGOW_HASKELL__
42    readListDefault,     -- :: Read a => ReadS [a]
43    readListPrecDefault, -- :: Read a => ReadPrec [a]
44 #endif
45
46  ) where
47
48 #ifdef __GLASGOW_HASKELL__
49 import GHC.Base
50 import GHC.Read
51 import Data.Either
52 import Text.ParserCombinators.ReadP as P
53 #endif
54 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
55 import Text.ParserCombinators.ReadPrec
56 import qualified Text.Read.Lex as L
57 #endif
58
59 #ifdef __HUGS__
60 -- copied from GHC.Read
61
62 lexP :: ReadPrec L.Lexeme
63 lexP = lift L.lex
64
65 parens :: ReadPrec a -> ReadPrec a
66 parens p = optional
67  where
68   optional  = p +++ mandatory
69   mandatory = do
70     L.Punc "(" <- lexP
71     x          <- reset optional
72     L.Punc ")" <- lexP
73     return x
74 #endif
75
76 #ifdef __GLASGOW_HASKELL__
77 ------------------------------------------------------------------------
78 -- utility functions
79
80 -- | equivalent to 'readsPrec' with a precedence of 0.
81 reads :: Read a => ReadS a
82 reads = readsPrec minPrec
83
84 readEither :: Read a => String -> Either String a
85 readEither s =
86   case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of
87     [x] -> Right x
88     []  -> Left "Prelude.read: no parse"
89     _   -> Left "Prelude.read: ambiguous parse"
90  where
91   read' =
92     do x <- readPrec
93        lift P.skipSpaces
94        return x
95
96 -- | The 'read' function reads input from a string, which must be
97 -- completely consumed by the input process.
98 read :: Read a => String -> a
99 read s = either error id (readEither s)
100 #endif
101