From: ross Date: Mon, 28 Apr 2003 09:16:48 +0000 (+0000) Subject: [project @ 2003-04-28 09:16:47 by ross] X-Git-Tag: nhc98-1-18-release~664 X-Git-Url: http://git.megacz.com/?a=commitdiff_plain;h=3512235d9503c23c0f37ea4f82d9f9db08d4e894;p=ghc-base.git [project @ 2003-04-28 09:16:47 by ross] portability fixes, plus marking these as non-portable (uses forall). --- diff --git a/Text/ParserCombinators/ReadP.hs b/Text/ParserCombinators/ReadP.hs index 32b6cfc..c05b983 100644 --- a/Text/ParserCombinators/ReadP.hs +++ b/Text/ParserCombinators/ReadP.hs @@ -7,7 +7,7 @@ -- -- Maintainer : libraries@haskell.org -- Stability : provisional --- Portability : portable +-- Portability : non-portable (local universal quantification) -- -- This is a library of parser combinators, originally written by Koen Claessen. -- It parses all alternatives in parallel, so it never keeps hold of @@ -49,14 +49,20 @@ module Text.ParserCombinators.ReadP where import Control.Monad( MonadPlus(..) ) +#ifdef __GLASGOW_HASKELL__ import GHC.Show( isSpace ) import GHC.Base +#else +import Data.Char( isSpace ) +#endif infixr 5 +++, <++ +#ifdef __GLASGOW_HASKELL__ -- We define a local version of ReadS here, -- because its "real" definition site is in GHC.Read type ReadS a = String -> [(a,String)] +#endif -- --------------------------------------------------------------------------- -- The P type @@ -170,6 +176,7 @@ R f1 +++ R f2 = R (\k -> f1 k `mplus` f2 k) -- ^ Local, exclusive, left-biased choice: If left parser -- locally produces any result at all, then right parser is -- not used. +#ifdef __GLASGOW_HASKELL__ R f <++ q = do s <- look probe (f return) s 0# @@ -182,6 +189,20 @@ R f <++ q = discard 0# = return () discard n = get >> discard (n-#1#) +#else +R f <++ q = + do s <- look + probe (f return) s 0 + where + probe (Get f) (c:s) n = probe (f c) s (n+1) + probe (Look f) s n = probe (f s) s n + probe p@(Result _ _) _ n = discard n >> R (p >>=) + probe (Final r) _ _ = R (Final r >>=) + probe _ _ _ = q + + discard 0 = return () + discard n = get >> discard (n-1) +#endif gather :: ReadP a -> ReadP (String, a) -- ^ Transforms a parser into one that does the same, but diff --git a/Text/ParserCombinators/ReadPrec.hs b/Text/ParserCombinators/ReadPrec.hs index 77cd61e..3c33bb1 100644 --- a/Text/ParserCombinators/ReadPrec.hs +++ b/Text/ParserCombinators/ReadPrec.hs @@ -7,7 +7,7 @@ -- -- Maintainer : libraries@haskell.org -- Stability : provisional --- Portability : portable +-- Portability : non-portable (uses Text.ParserCombinators.ReadP) -- -- This library defines parser combinators for precedence parsing. @@ -58,8 +58,10 @@ import qualified Text.ParserCombinators.ReadP as ReadP ) import Control.Monad( MonadPlus(..) ) +#ifdef __GLASGOW_HASKELL__ import GHC.Num( Num(..) ) import GHC.Base +#endif -- --------------------------------------------------------------------------- -- The readPrec type @@ -130,9 +132,11 @@ choice ps = foldr (+++) pfail ps -- --------------------------------------------------------------------------- -- Converting between ReadPrec and Read +#ifdef __GLASGOW_HASKELL__ -- We define a local version of ReadS here, -- because its "real" definition site is in GHC.Read type ReadS a = String -> [(a,String)] +#endif readPrec_to_P :: ReadPrec a -> (Int -> ReadP a) readPrec_to_P (P f) = f diff --git a/Text/Read/Lex.hs b/Text/Read/Lex.hs index dd26cb1..9be4220 100644 --- a/Text/Read/Lex.hs +++ b/Text/Read/Lex.hs @@ -7,7 +7,7 @@ -- -- Maintainer : libraries@haskell.org -- Stability : provisional --- Portability : portable +-- Portability : non-portable (uses Text.ParserCombinators.ReadP) -- -- The cut-down Haskell lexer, used by Text.Read -- @@ -31,6 +31,7 @@ module Text.Read.Lex import Text.ParserCombinators.ReadP +#ifdef __GLASGOW_HASKELL__ import GHC.Base import GHC.Num( Num(..), Integer ) import GHC.Show( Show(.. ), isSpace, isAlpha, isAlphaNum ) @@ -38,6 +39,14 @@ import GHC.Real( Ratio(..), Integral, Rational, (%), fromIntegral, toInteger, (^), (^^), infinity, notANumber ) import GHC.List import GHC.Enum( maxBound ) +#else +import Prelude hiding ( lex ) +import Data.Char( chr, ord, isSpace, isAlpha, isAlphaNum ) +import Data.Ratio( Ratio, (%) ) +#endif +#ifdef __HUGS__ +import Hugs.Prelude( Ratio(..) ) +#endif import Data.Maybe import Control.Monad @@ -127,6 +136,12 @@ lexId = lex_nan <++ lex_id isIdsChar c = isAlpha c || c == '_' isIdfChar c = isAlphaNum c || c `elem` "_'" +#ifndef __GLASGOW_HASKELL__ +infinity, notANumber :: Rational +infinity = 1 :% 0 +notANumber = 0 :% 0 +#endif + -- --------------------------------------------------------------------------- -- Lexing character literals