{-# LANGUAGE OverloadedStrings, CPP #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif

-- |
-- Module      : Data.Text.Lazy.Read
-- Copyright   : (c) 2010, 2011 Bryan O'Sullivan
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Portability : GHC
--
-- Functions used frequently when reading textual data.
module Data.Text.Lazy.Read
    (
      Reader
    , decimal
    , hexadecimal
    , signed
    , rational
    , double
    ) where

import Control.Monad (liftM)
import Data.Char (isDigit, isHexDigit)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Ratio ((%))
import Data.Text.Internal.Read
import Data.Text.Lazy as T
import Data.Word (Word, Word8, Word16, Word32, Word64)

-- | Read some text.  If the read succeeds, return its value and the
-- remaining text, otherwise an error message.
type Reader a = IReader Text a
type Parser = IParser Text

-- | Read a decimal integer.  The input must begin with at least one
-- decimal digit, and is consumed until a non-digit or end of string
-- is reached.
--
-- This function does not handle leading sign characters.  If you need
-- to handle signed input, use @'signed' 'decimal'@.
--
-- /Note/: For fixed-width integer types, this function does not
-- attempt to detect overflow, so a sufficiently long input may give
-- incorrect results.  If you are worried about overflow, use
-- 'Integer' for your result type.
decimal :: Integral a => Reader a
{-# SPECIALIZE decimal :: Reader Int #-}
{-# SPECIALIZE decimal :: Reader Int8 #-}
{-# SPECIALIZE decimal :: Reader Int16 #-}
{-# SPECIALIZE decimal :: Reader Int32 #-}
{-# SPECIALIZE decimal :: Reader Int64 #-}
{-# SPECIALIZE decimal :: Reader Integer #-}
{-# SPECIALIZE decimal :: Reader Data.Word.Word #-}
{-# SPECIALIZE decimal :: Reader Word8 #-}
{-# SPECIALIZE decimal :: Reader Word16 #-}
{-# SPECIALIZE decimal :: Reader Word32 #-}
{-# SPECIALIZE decimal :: Reader Word64 #-}
decimal :: Reader a
decimal Text
txt
    | Text -> Bool
T.null Text
h  = String -> Either String (a, Text)
forall a b. a -> Either a b
Left String
"input does not start with a digit"
    | Bool
otherwise = (a, Text) -> Either String (a, Text)
forall a b. b -> Either a b
Right ((a -> Char -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' a -> Char -> a
forall a. Num a => a -> Char -> a
go a
0 Text
h, Text
t)
  where (Text
h,Text
t)  = (Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
isDigit Text
txt
        go :: a -> Char -> a
go a
n Char
d = (a
n a -> a -> a
forall a. Num a => a -> a -> a
* a
10 a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
digitToInt Char
d))

-- | Read a hexadecimal integer, consisting of an optional leading
-- @\"0x\"@ followed by at least one hexadecimal digit. Input is
-- consumed until a non-hex-digit or end of string is reached.
-- This function is case insensitive.
--
-- This function does not handle leading sign characters.  If you need
-- to handle signed input, use @'signed' 'hexadecimal'@.
--
-- /Note/: For fixed-width integer types, this function does not
-- attempt to detect overflow, so a sufficiently long input may give
-- incorrect results.  If you are worried about overflow, use
-- 'Integer' for your result type.
hexadecimal :: Integral a => Reader a
{-# SPECIALIZE hexadecimal :: Reader Int #-}
{-# SPECIALIZE hexadecimal :: Reader Integer #-}
hexadecimal :: Reader a
hexadecimal Text
txt
    | Text
h Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"0x" Bool -> Bool -> Bool
|| Text
h Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"0X" = Reader a
forall a. Integral a => Reader a
hex Text
t
    | Bool
otherwise              = Reader a
forall a. Integral a => Reader a
hex Text
txt
 where (Text
h,Text
t) = Int64 -> Text -> (Text, Text)
T.splitAt Int64
2 Text
txt

hex :: Integral a => Reader a
{-# SPECIALIZE hexadecimal :: Reader Int #-}
{-# SPECIALIZE hexadecimal :: Reader Int8 #-}
{-# SPECIALIZE hexadecimal :: Reader Int16 #-}
{-# SPECIALIZE hexadecimal :: Reader Int32 #-}
{-# SPECIALIZE hexadecimal :: Reader Int64 #-}
{-# SPECIALIZE hexadecimal :: Reader Integer #-}
{-# SPECIALIZE hexadecimal :: Reader Word #-}
{-# SPECIALIZE hexadecimal :: Reader Word8 #-}
{-# SPECIALIZE hexadecimal :: Reader Word16 #-}
{-# SPECIALIZE hexadecimal :: Reader Word32 #-}
{-# SPECIALIZE hexadecimal :: Reader Word64 #-}
hex :: Reader a
hex Text
txt
    | Text -> Bool
T.null Text
h  = String -> Either String (a, Text)
forall a b. a -> Either a b
Left String
"input does not start with a hexadecimal digit"
    | Bool
otherwise = (a, Text) -> Either String (a, Text)
forall a b. b -> Either a b
Right ((a -> Char -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' a -> Char -> a
forall a. Num a => a -> Char -> a
go a
0 Text
h, Text
t)
  where (Text
h,Text
t)  = (Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
isHexDigit Text
txt
        go :: a -> Char -> a
go a
n Char
d = (a
n a -> a -> a
forall a. Num a => a -> a -> a
* a
16 a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
hexDigitToInt Char
d))

-- | Read an optional leading sign character (@\'-\'@ or @\'+\'@) and
-- apply it to the result of applying the given reader.
signed :: Num a => Reader a -> Reader a
{-# INLINE signed #-}
signed :: Reader a -> Reader a
signed Reader a
f = IParser Text a -> Reader a
forall t a. IParser t a -> IReader t a
runP (IParser Text a -> IParser Text a
forall a. Num a => Parser a -> Parser a
signa (Reader a -> IParser Text a
forall t a. IReader t a -> IParser t a
P Reader a
f))

-- | Read a rational number.
--
-- This function accepts an optional leading sign character, followed
-- by at least one decimal digit.  The syntax similar to that accepted
-- by the 'read' function, with the exception that a trailing @\'.\'@
-- or @\'e\'@ /not/ followed by a number is not consumed.
--
-- Examples:
--
-- >rational "3"     == Right (3.0, "")
-- >rational "3.1"   == Right (3.1, "")
-- >rational "3e4"   == Right (30000.0, "")
-- >rational "3.1e4" == Right (31000.0, "")
-- >rational ".3"    == Left "input does not start with a digit"
-- >rational "e3"    == Left "input does not start with a digit"
--
-- Examples of differences from 'read':
--
-- >rational "3.foo" == Right (3.0, ".foo")
-- >rational "3e"    == Right (3.0, "e")
rational :: Fractional a => Reader a
{-# SPECIALIZE rational :: Reader Double #-}
rational :: Reader a
rational = (Integer -> Integer -> Integer -> a) -> Reader a
forall a.
Fractional a =>
(Integer -> Integer -> Integer -> a) -> Reader a
floaty ((Integer -> Integer -> Integer -> a) -> Reader a)
-> (Integer -> Integer -> Integer -> a) -> Reader a
forall a b. (a -> b) -> a -> b
$ \Integer
real Integer
frac Integer
fracDenom -> Rational -> a
forall a. Fractional a => Rational -> a
fromRational (Rational -> a) -> Rational -> a
forall a b. (a -> b) -> a -> b
$
                     Integer
real Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1 Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Integer
frac Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
fracDenom

-- | Read a rational number.
--
-- The syntax accepted by this function is the same as for 'rational'.
--
-- /Note/: This function is almost ten times faster than 'rational',
-- but is slightly less accurate.
--
-- The 'Double' type supports about 16 decimal places of accuracy.
-- For 94.2% of numbers, this function and 'rational' give identical
-- results, but for the remaining 5.8%, this function loses precision
-- around the 15th decimal place.  For 0.001% of numbers, this
-- function will lose precision at the 13th or 14th decimal place.
double :: Reader Double
double :: Reader Double
double = (Integer -> Integer -> Integer -> Double) -> Reader Double
forall a.
Fractional a =>
(Integer -> Integer -> Integer -> a) -> Reader a
floaty ((Integer -> Integer -> Integer -> Double) -> Reader Double)
-> (Integer -> Integer -> Integer -> Double) -> Reader Double
forall a b. (a -> b) -> a -> b
$ \Integer
real Integer
frac Integer
fracDenom ->
                   Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
real Double -> Double -> Double
forall a. Num a => a -> a -> a
+
                   Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
frac Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
fracDenom

signa :: Num a => Parser a -> Parser a
{-# SPECIALIZE signa :: Parser Int -> Parser Int #-}
{-# SPECIALIZE signa :: Parser Int8 -> Parser Int8 #-}
{-# SPECIALIZE signa :: Parser Int16 -> Parser Int16 #-}
{-# SPECIALIZE signa :: Parser Int32 -> Parser Int32 #-}
{-# SPECIALIZE signa :: Parser Int64 -> Parser Int64 #-}
{-# SPECIALIZE signa :: Parser Integer -> Parser Integer #-}
signa :: Parser a -> Parser a
signa Parser a
p = do
  Char
sign <- Char -> IParser Text Char -> IParser Text Char
forall a t. a -> IParser t a -> IParser t a
perhaps Char
'+' (IParser Text Char -> IParser Text Char)
-> IParser Text Char -> IParser Text Char
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> IParser Text Char
char (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+')
  if Char
sign Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+' then Parser a
p else a -> a
forall a. Num a => a -> a
negate (a -> a) -> Parser a -> Parser a
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Parser a
p

char :: (Char -> Bool) -> Parser Char
char :: (Char -> Bool) -> IParser Text Char
char Char -> Bool
p = IReader Text Char -> IParser Text Char
forall t a. IReader t a -> IParser t a
P (IReader Text Char -> IParser Text Char)
-> IReader Text Char -> IParser Text Char
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Maybe (Char, Text)
T.uncons Text
t of
                     Just (Char
c,Text
t') | Char -> Bool
p Char
c -> (Char, Text) -> Either String (Char, Text)
forall a b. b -> Either a b
Right (Char
c,Text
t')
                     Maybe (Char, Text)
_                 -> String -> Either String (Char, Text)
forall a b. a -> Either a b
Left String
"character does not match"

floaty :: Fractional a => (Integer -> Integer -> Integer -> a) -> Reader a
{-# INLINE floaty #-}
floaty :: (Integer -> Integer -> Integer -> a) -> Reader a
floaty Integer -> Integer -> Integer -> a
f = IParser Text a -> Reader a
forall t a. IParser t a -> IReader t a
runP (IParser Text a -> Reader a) -> IParser Text a -> Reader a
forall a b. (a -> b) -> a -> b
$ do
  Char
sign <- Char -> IParser Text Char -> IParser Text Char
forall a t. a -> IParser t a -> IParser t a
perhaps Char
'+' (IParser Text Char -> IParser Text Char)
-> IParser Text Char -> IParser Text Char
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> IParser Text Char
char (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+')
  Integer
real <- IReader Text Integer -> IParser Text Integer
forall t a. IReader t a -> IParser t a
P IReader Text Integer
forall a. Integral a => Reader a
decimal
  T Integer
fraction Int
fracDigits <- T -> IParser Text T -> IParser Text T
forall a t. a -> IParser t a -> IParser t a
perhaps (Integer -> Int -> T
T Integer
0 Int
0) (IParser Text T -> IParser Text T)
-> IParser Text T -> IParser Text T
forall a b. (a -> b) -> a -> b
$ do
    Char
_ <- (Char -> Bool) -> IParser Text Char
char (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'.')
    Int
digits <- IReader Text Int -> IParser Text Int
forall t a. IReader t a -> IParser t a
P (IReader Text Int -> IParser Text Int)
-> IReader Text Int -> IParser Text Int
forall a b. (a -> b) -> a -> b
$ \Text
t -> (Int, Text) -> Either String (Int, Text)
forall a b. b -> Either a b
Right (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> (Text -> Int64) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int64
T.length (Text -> Int) -> Text -> Int
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.takeWhile Char -> Bool
isDigit Text
t, Text
t)
    Integer
n <- IReader Text Integer -> IParser Text Integer
forall t a. IReader t a -> IParser t a
P IReader Text Integer
forall a. Integral a => Reader a
decimal
    T -> IParser Text T
forall (m :: * -> *) a. Monad m => a -> m a
return (T -> IParser Text T) -> T -> IParser Text T
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> T
T Integer
n Int
digits
  let e :: Char -> Bool
e Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'e' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'E'
  Int
power <- Int -> IParser Text Int -> IParser Text Int
forall a t. a -> IParser t a -> IParser t a
perhaps Int
0 ((Char -> Bool) -> IParser Text Char
char Char -> Bool
e IParser Text Char -> IParser Text Int -> IParser Text Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IParser Text Int -> IParser Text Int
forall a. Num a => Parser a -> Parser a
signa (IReader Text Int -> IParser Text Int
forall t a. IReader t a -> IParser t a
P IReader Text Int
forall a. Integral a => Reader a
decimal) :: Parser Int)
  let n :: a
n = if Int
fracDigits Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
          then if Int
power Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
               then Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
real
               else Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
real a -> a -> a
forall a. Num a => a -> a -> a
* (a
10 a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Int
power)
          else if Int
power Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
               then Integer -> Integer -> Integer -> a
f Integer
real Integer
fraction (Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
fracDigits)
               else Integer -> Integer -> Integer -> a
f Integer
real Integer
fraction (Integer
10 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
fracDigits) a -> a -> a
forall a. Num a => a -> a -> a
* (a
10 a -> Int -> a
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Int
power)
  a -> IParser Text a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> IParser Text a) -> a -> IParser Text a
forall a b. (a -> b) -> a -> b
$! if Char
sign Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'+'
            then a
n
            else -a
n