Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Text / ParserCombinators / ReadPrec.hs
index b501a8e..f282d1a 100644 (file)
@@ -1,4 +1,5 @@
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# LANGUAGE CPP, NoImplicitPrelude #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Text.ParserCombinators.ReadPrec
@@ -7,8 +8,10 @@
 -- 
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  provisional
--- Portability :  portable
+-- Portability :  non-portable (uses Text.ParserCombinators.ReadP)
 --
+-- This library defines parser combinators for precedence parsing.
+
 -----------------------------------------------------------------------------
 
 module Text.ParserCombinators.ReadPrec
@@ -19,20 +22,22 @@ module Text.ParserCombinators.ReadPrec
   Prec,          -- :: *; = Int
   minPrec,       -- :: Prec; = 0
 
-  -- * Primitive operations
+  -- * Precedence operations
   lift,          -- :: ReadP a -> ReadPrec a
   prec,          -- :: Prec -> ReadPrec a -> ReadPrec a
   step,          -- :: ReadPrec a -> ReadPrec a
   reset,         -- :: ReadPrec a -> ReadPrec a
 
   -- * Other operations
+  -- | All are based directly on their similarly-named 'ReadP' counterparts.
   get,           -- :: ReadPrec Char
   look,          -- :: ReadPrec String
   (+++),         -- :: ReadPrec a -> ReadPrec a -> ReadPrec a
+  (<++),         -- :: ReadPrec a -> ReadPrec a -> ReadPrec a
   pfail,         -- :: ReadPrec a
   choice,        -- :: [ReadPrec a] -> ReadPrec a
 
-  -- converters
+  -- * Converters
   readPrec_to_P, -- :: ReadPrec a       -> (Int -> ReadP a)
   readP_to_Prec, -- :: (Int -> ReadP a) -> ReadPrec a
   readPrec_to_S, -- :: ReadPrec a       -> (Int -> ReadS a)
@@ -43,6 +48,7 @@ module Text.ParserCombinators.ReadPrec
 
 import Text.ParserCombinators.ReadP
   ( ReadP
+  , ReadS
   , readP_to_S
   , readS_to_P
   )
@@ -50,19 +56,20 @@ import Text.ParserCombinators.ReadP
 import qualified Text.ParserCombinators.ReadP as ReadP
   ( get
   , look
-  , (+++)
+  , (+++), (<++)
   , pfail
-  , choice
   )
 
 import Control.Monad( MonadPlus(..) )
+#ifdef __GLASGOW_HASKELL__
 import GHC.Num( Num(..) )
 import GHC.Base
+#endif
 
 -- ---------------------------------------------------------------------------
 -- The readPrec type
 
-newtype ReadPrec a = P { unP :: Prec -> ReadP a }
+newtype ReadPrec a = P (Prec -> ReadP a)
 
 -- Functor, Monad, MonadPlus
 
@@ -89,48 +96,60 @@ minPrec = 0
 -- Operations over ReadPrec
 
 lift :: ReadP a -> ReadPrec a
+-- ^ Lift a precedence-insensitive 'ReadP' to a 'ReadPrec'.
 lift m = P (\_ -> m)
 
 step :: ReadPrec a -> ReadPrec a
--- Increases the precedence context by one
+-- ^ Increases the precedence context by one.
 step (P f) = P (\n -> f (n+1))
 
 reset :: ReadPrec a -> ReadPrec a
--- Resets the precedence context to zero
-reset (P f) = P (\n -> f minPrec)
+-- ^ Resets the precedence context to zero.
+reset (P f) = P (\_ -> f minPrec)
 
 prec :: Prec -> ReadPrec a -> ReadPrec a
--- (prec n p) checks that the precedence context is 
---                       less than or equal to n,
---     if not, fails
---     if so, parses p in context n
+-- ^ @(prec n p)@ checks whether the precedence context is 
+--   less than or equal to @n@, and
+--
+--   * if not, fails
+--
+--   * if so, parses @p@ in context @n@.
 prec n (P f) = P (\c -> if c <= n then f n else ReadP.pfail)
 
 -- ---------------------------------------------------------------------------
 -- Derived operations
 
 get :: ReadPrec Char
+-- ^ Consumes and returns the next character.
+--   Fails if there is no input left.
 get = lift ReadP.get
 
 look :: ReadPrec String
+-- ^ Look-ahead: returns the part of the input that is left, without
+--   consuming it.
 look = lift ReadP.look
 
 (+++) :: ReadPrec a -> ReadPrec a -> ReadPrec a
+-- ^ Symmetric choice.
 P f1 +++ P f2 = P (\n -> f1 n ReadP.+++ f2 n)
 
+(<++) :: ReadPrec a -> ReadPrec a -> ReadPrec a
+-- ^ Local, exclusive, left-biased choice: If left parser
+--   locally produces any result at all, then right parser is
+--   not used.
+P f1 <++ P f2 = P (\n -> f1 n ReadP.<++ f2 n)
+
 pfail :: ReadPrec a
+-- ^ Always fails.
 pfail = lift ReadP.pfail
 
 choice :: [ReadPrec a] -> ReadPrec a
+-- ^ Combines all parsers in the specified list.
 choice ps = foldr (+++) pfail ps
 
 -- ---------------------------------------------------------------------------
 -- Converting between ReadPrec and Read
 
--- We define a local version of ReadS here,
--- because its "real" definition site is in GHC.Read
-type ReadS a = String -> [(a,String)]
-
 readPrec_to_P :: ReadPrec a -> (Int -> ReadP a)
 readPrec_to_P (P f) = f