summaryrefslogtreecommitdiff
path: root/libraries/base/Text
diff options
context:
space:
mode:
authorKavon Farvardin <kavon@farvard.in>2018-09-23 15:29:37 -0500
committerKavon Farvardin <kavon@farvard.in>2018-09-23 15:29:37 -0500
commit84c2ad99582391005b5e873198b15e9e9eb4f78d (patch)
treecaa8c2f2ec7e97fbb4977263c6817c9af5025cf4 /libraries/base/Text
parent8ddb47cfcf5776e9a3c55fd37947c8a95e00fa12 (diff)
parente68b439fe5de61b9a2ca51af472185c62ccb8b46 (diff)
downloadhaskell-wip/T13904.tar.gz
update to current master againwip/T13904
Diffstat (limited to 'libraries/base/Text')
-rw-r--r--libraries/base/Text/ParserCombinators/ReadP.hs129
-rw-r--r--libraries/base/Text/Printf.hs100
-rw-r--r--libraries/base/Text/Read.hs22
-rw-r--r--libraries/base/Text/Read/Lex.hs10
4 files changed, 130 insertions, 131 deletions
diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs
index fd7c677bd9..063c08910a 100644
--- a/libraries/base/Text/ParserCombinators/ReadP.hs
+++ b/libraries/base/Text/ParserCombinators/ReadP.hs
@@ -100,7 +100,7 @@ data P a
| Fail
| Result a (P a)
| Final [(a,String)] -- invariant: list is non-empty!
- deriving Functor
+ deriving Functor -- ^ @since 4.8.0.0
-- Monad, MonadPlus
@@ -161,8 +161,6 @@ instance Alternative P where
newtype ReadP a = R (forall b . (a -> P b) -> P b)
--- Functor, Monad, MonadPlus
-
-- | @since 2.01
instance Functor ReadP where
fmap h (R f) = R (\k -> f (k . h))
@@ -171,7 +169,7 @@ instance Functor ReadP where
instance Applicative ReadP where
pure x = R (\k -> k x)
(<*>) = ap
- liftA2 = liftM2
+ -- liftA2 = liftM2
-- | @since 2.01
instance Monad ReadP where
@@ -439,85 +437,68 @@ The following are QuickCheck specifications of what the combinators do.
These can be seen as formal specifications of the behavior of the
combinators.
-We use bags to give semantics to the combinators.
+For some values, we only care about the lists contents, not their order,
-> type Bag a = [a]
+> (=~) :: Ord a => [a] -> [a] -> Bool
+> xs =~ ys = sort xs == sort ys
-Equality on bags does not care about the order of elements.
+Here follow the properties:
-> (=~) :: Ord a => Bag a -> Bag a -> Bool
-> xs =~ ys = sort xs == sort ys
+>>> readP_to_S get []
+[]
-A special equality operator to avoid unresolved overloading
-when testing the properties.
+prop> \c str -> readP_to_S get (c:str) == [(c, str)]
-> (=~.) :: Bag (Int,String) -> Bag (Int,String) -> Bool
-> (=~.) = (=~)
+prop> \str -> readP_to_S look str == [(str, str)]
-Here follow the properties:
+prop> \str -> readP_to_S pfail str == []
-> prop_Get_Nil =
-> readP_to_S get [] =~ []
->
-> prop_Get_Cons c s =
-> readP_to_S get (c:s) =~ [(c,s)]
->
-> prop_Look s =
-> readP_to_S look s =~ [(s,s)]
->
-> prop_Fail s =
-> readP_to_S pfail s =~. []
->
-> prop_Return x s =
-> readP_to_S (return x) s =~. [(x,s)]
->
-> prop_Bind p k s =
-> readP_to_S (p >>= k) s =~.
+prop> \x str -> readP_to_S (return x) s == [(x,s)]
+
+> prop_Bind p k s =
+> readP_to_S (p >>= k) s =~
> [ ys''
> | (x,s') <- readP_to_S p s
> , ys'' <- readP_to_S (k (x::Int)) s'
> ]
->
-> prop_Plus p q s =
-> readP_to_S (p +++ q) s =~.
-> (readP_to_S p s ++ readP_to_S q s)
->
-> prop_LeftPlus p q s =
-> readP_to_S (p <++ q) s =~.
-> (readP_to_S p s +<+ readP_to_S q s)
-> where
-> [] +<+ ys = ys
-> xs +<+ _ = xs
->
-> prop_Gather s =
-> forAll readPWithoutReadS $ \p ->
-> readP_to_S (gather p) s =~
-> [ ((pre,x::Int),s')
-> | (x,s') <- readP_to_S p s
-> , let pre = take (length s - length s') s
-> ]
->
-> prop_String_Yes this s =
-> readP_to_S (string this) (this ++ s) =~
-> [(this,s)]
->
-> prop_String_Maybe this s =
-> readP_to_S (string this) s =~
-> [(this, drop (length this) s) | this `isPrefixOf` s]
->
-> prop_Munch p s =
-> readP_to_S (munch p) s =~
-> [(takeWhile p s, dropWhile p s)]
->
-> prop_Munch1 p s =
-> readP_to_S (munch1 p) s =~
-> [(res,s') | let (res,s') = (takeWhile p s, dropWhile p s), not (null res)]
->
-> prop_Choice ps s =
-> readP_to_S (choice ps) s =~.
-> readP_to_S (foldr (+++) pfail ps) s
->
-> prop_ReadS r s =
-> readP_to_S (readS_to_P r) s =~. r s
--}
+> prop_Plus p q s =
+> readP_to_S (p +++ q) s =~
+> (readP_to_S p s ++ readP_to_S q s)
+
+> prop_LeftPlus p q s =
+> readP_to_S (p <++ q) s =~
+> (readP_to_S p s +<+ readP_to_S q s)
+> where
+> [] +<+ ys = ys
+> xs +<+ _ = xs
+
+> prop_Gather s =
+> forAll readPWithoutReadS $ \p ->
+> readP_to_S (gather p) s =~
+> [ ((pre,x::Int),s')
+> | (x,s') <- readP_to_S p s
+> , let pre = take (length s - length s') s
+> ]
+
+prop> \this str -> readP_to_S (string this) (this ++ str) == [(this,str)]
+
+> prop_String_Maybe this s =
+> readP_to_S (string this) s =~
+> [(this, drop (length this) s) | this `isPrefixOf` s]
+
+> prop_Munch p s =
+> readP_to_S (munch p) s =~
+> [(takeWhile p s, dropWhile p s)]
+
+> prop_Munch1 p s =
+> readP_to_S (munch1 p) s =~
+> [(res,s') | let (res,s') = (takeWhile p s, dropWhile p s), not (null res)]
+
+> prop_Choice ps s =
+> readP_to_S (choice ps) s =~
+> readP_to_S (foldr (+++) pfail ps) s
+
+> prop_ReadS r s =
+> readP_to_S (readS_to_P r) s =~ r s
+-}
diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs
index 0914aa7b5c..177e8f2230 100644
--- a/libraries/base/Text/Printf.hs
+++ b/libraries/base/Text/Printf.hs
@@ -102,6 +102,10 @@ import System.IO
-------------------
-- | Format a variable number of arguments with the C-style formatting string.
+--
+-- >>> printf "%s, %d, %.4f" "hello" 123 pi
+-- hello, 123, 3.1416
+--
-- The return value is either 'String' or @('IO' a)@ (which
-- should be @('IO' '()')@, but Haskell's type system
-- makes this hard).
@@ -133,11 +137,11 @@ import System.IO
-- A conversion specification begins with the
-- character @%@, followed by zero or more of the following flags:
--
--- > - left adjust (default is right adjust)
--- > + always use a sign (+ or -) for signed conversions
--- > space leading space for positive numbers in signed conversions
--- > 0 pad with zeros rather than spaces
--- > # use an \"alternate form\": see below
+-- > - left adjust (default is right adjust)
+-- > + always use a sign (+ or -) for signed conversions
+-- > space leading space for positive numbers in signed conversions
+-- > 0 pad with zeros rather than spaces
+-- > # use an \"alternate form\": see below
--
-- When both flags are given, @-@ overrides @0@ and @+@ overrides space.
-- A negative width specifier in a @*@ conversion is treated as
@@ -146,32 +150,32 @@ import System.IO
-- The \"alternate form\" for unsigned radix conversions is
-- as in C @printf(3)@:
--
--- > %o prefix with a leading 0 if needed
--- > %x prefix with a leading 0x if nonzero
--- > %X prefix with a leading 0X if nonzero
--- > %b prefix with a leading 0b if nonzero
--- > %[eEfFgG] ensure that the number contains a decimal point
+-- > %o prefix with a leading 0 if needed
+-- > %x prefix with a leading 0x if nonzero
+-- > %X prefix with a leading 0X if nonzero
+-- > %b prefix with a leading 0b if nonzero
+-- > %[eEfFgG] ensure that the number contains a decimal point
--
-- Any flags are followed optionally by a field width:
--
--- > num field width
--- > * as num, but taken from argument list
+-- > num field width
+-- > * as num, but taken from argument list
--
-- The field width is a minimum, not a maximum: it will be
-- expanded as needed to avoid mutilating a value.
--
-- Any field width is followed optionally by a precision:
--
--- > .num precision
--- > . same as .0
--- > .* as num, but taken from argument list
+-- > .num precision
+-- > . same as .0
+-- > .* as num, but taken from argument list
--
-- Negative precision is taken as 0. The meaning of the
-- precision depends on the conversion type.
--
--- > Integral minimum number of digits to show
--- > RealFloat number of digits after the decimal point
--- > String maximum number of characters
+-- > Integral minimum number of digits to show
+-- > RealFloat number of digits after the decimal point
+-- > String maximum number of characters
--
-- The precision for Integral types is accomplished by zero-padding.
-- If both precision and zero-pad are given for an Integral field,
@@ -182,29 +186,29 @@ import System.IO
-- to set the implicit size of the operand for conversion of
-- a negative operand to unsigned:
--
--- > hh Int8
--- > h Int16
--- > l Int32
--- > ll Int64
--- > L Int64
+-- > hh Int8
+-- > h Int16
+-- > l Int32
+-- > ll Int64
+-- > L Int64
--
-- The specification ends with a format character:
--
--- > c character Integral
--- > d decimal Integral
--- > o octal Integral
--- > x hexadecimal Integral
--- > X hexadecimal Integral
--- > b binary Integral
--- > u unsigned decimal Integral
--- > f floating point RealFloat
--- > F floating point RealFloat
--- > g general format float RealFloat
--- > G general format float RealFloat
--- > e exponent format float RealFloat
--- > E exponent format float RealFloat
--- > s string String
--- > v default format any type
+-- > c character Integral
+-- > d decimal Integral
+-- > o octal Integral
+-- > x hexadecimal Integral
+-- > X hexadecimal Integral
+-- > b binary Integral
+-- > u unsigned decimal Integral
+-- > f floating point RealFloat
+-- > F floating point RealFloat
+-- > g general format float RealFloat
+-- > G general format float RealFloat
+-- > e exponent format float RealFloat
+-- > E exponent format float RealFloat
+-- > s string String
+-- > v default format any type
--
-- The \"%v\" specifier is provided for all built-in types,
-- and should be provided for user-defined type formatters
@@ -212,11 +216,11 @@ import System.IO
-- type. For the built-in types the \"%v\" specifier is
-- converted as follows:
--
--- > c Char
--- > u other unsigned Integral
--- > d other signed Integral
--- > g RealFloat
--- > s String
+-- > c Char
+-- > u other unsigned Integral
+-- > d other signed Integral
+-- > g RealFloat
+-- > s String
--
-- Mismatch between the argument types and the format
-- string, as well as any other syntactic or semantic errors
@@ -246,16 +250,6 @@ import System.IO
--
-- * Haskell 'printf' will place a zero after a decimal point when
-- possible.
---
--- ==== __Examples__
---
--- > > printf "%d\n" (23::Int)
--- > 23
--- > > printf "%s %s\n" "Hello" "World"
--- > Hello World
--- > > printf "%.2f\n" pi
--- > 3.14
---
printf :: (PrintfType r) => String -> r
printf fmts = spr fmts []
diff --git a/libraries/base/Text/Read.hs b/libraries/base/Text/Read.hs
index 2479eb529a..c79b7c15b2 100644
--- a/libraries/base/Text/Read.hs
+++ b/libraries/base/Text/Read.hs
@@ -62,6 +62,12 @@ reads = readsPrec minPrec
-- Succeeds if there is exactly one valid result.
-- A 'Left' value indicates a parse error.
--
+-- >>> readEither "123" :: Either String Int
+-- Right 123
+--
+-- >>> readEither "hello" :: Either String Int
+-- Left "Prelude.read: no parse"
+--
-- @since 4.6.0.0
readEither :: Read a => String -> Either String a
readEither s =
@@ -78,6 +84,12 @@ readEither s =
-- | Parse a string using the 'Read' instance.
-- Succeeds if there is exactly one valid result.
--
+-- >>> readMaybe "123" :: Maybe Int
+-- Just 123
+--
+-- >>> readMaybe "hello" :: Maybe Int
+-- Nothing
+--
-- @since 4.6.0.0
readMaybe :: Read a => String -> Maybe a
readMaybe s = case readEither s of
@@ -85,6 +97,14 @@ readMaybe s = case readEither s of
Right a -> Just a
-- | The 'read' function reads input from a string, which must be
--- completely consumed by the input process.
+-- completely consumed by the input process. 'read' fails with an 'error' if the
+-- parse is unsuccessful, and it is therefore discouraged from being used in
+-- real applications. Use 'readMaybe' or 'readEither' for safe alternatives.
+--
+-- >>> read "123" :: Int
+-- 123
+--
+-- >>> read "hello" :: Int
+-- *** Exception: Prelude.read: no parse
read :: Read a => String -> a
read s = either errorWithoutStackTrace id (readEither s)
diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs
index d0d39c6648..7568f9afaf 100644
--- a/libraries/base/Text/Read/Lex.hs
+++ b/libraries/base/Text/Read/Lex.hs
@@ -68,15 +68,19 @@ data Lexeme
| Symbol String -- ^ Haskell symbol, e.g. @>>@, @:%@
| Number Number -- ^ @since 4.6.0.0
| EOF
- deriving (Eq, Show)
+ deriving ( Eq -- ^ @since 2.01
+ , Show -- ^ @since 2.01
+ )
--- | @since 4.7.0.0
+-- | @since 4.6.0.0
data Number = MkNumber Int -- Base
Digits -- Integral part
| MkDecimal Digits -- Integral part
(Maybe Digits) -- Fractional part
(Maybe Integer) -- Exponent
- deriving (Eq, Show)
+ deriving ( Eq -- ^ @since 4.6.0.0
+ , Show -- ^ @since 4.6.0.0
+ )
-- | @since 4.5.1.0
numberToInteger :: Number -> Maybe Integer