Skip to content

Commit

Permalink
Rename Lex to Read
Browse files Browse the repository at this point in the history
--HG--
extra : convert_revision : c0ad41f04418dcc15f4b71cfbd4ecd1e77b0d146
  • Loading branch information
bos committed Oct 10, 2010
1 parent 446eb32 commit b18bfc1
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 26 deletions.
38 changes: 19 additions & 19 deletions Data/Text/Lex.hs → Data/Text/Read.hs
Original file line number Original file line Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}


-- | -- |
-- Module : Data.Text.Lex -- Module : Data.Text.Read
-- Copyright : (c) 2010 Bryan O'Sullivan -- Copyright : (c) 2010 Bryan O'Sullivan
-- --
-- License : BSD-style -- License : BSD-style
Expand All @@ -10,10 +10,10 @@
-- Stability : experimental -- Stability : experimental
-- Portability : GHC -- Portability : GHC
-- --
-- Lexing functions used frequently when handling textual data. -- Reading functions used frequently when handling textual data.
module Data.Text.Lex module Data.Text.Read
( (
Lexer Reader
, decimal , decimal
, hexadecimal , hexadecimal
, signed , signed
Expand All @@ -28,15 +28,15 @@ import Data.Text as T


-- | Read some text, and if the read succeeds, return its value and -- | Read some text, and if the read succeeds, return its value and
-- the remaining text. -- the remaining text.
type Lexer a = Text -> Either String (a,Text) type Reader a = Text -> Either String (a,Text)


-- | Read a decimal integer. -- | Read a decimal integer.
-- --
-- This function does not handle leading sign characters. If you need -- This function does not handle leading sign characters. If you need
-- to handle signed input, use @'signed' 'decimal'@. -- to handle signed input, use @'signed' 'decimal'@.
decimal :: Integral a => Lexer a decimal :: Integral a => Reader a
{-# SPECIALIZE decimal :: Lexer Int #-} {-# SPECIALIZE decimal :: Reader Int #-}
{-# SPECIALIZE decimal :: Lexer Integer #-} {-# SPECIALIZE decimal :: Reader Integer #-}
decimal txt decimal txt
| T.null h = Left "no digits in input" | T.null h = Left "no digits in input"
| otherwise = Right (T.foldl' go 0 h, t) | otherwise = Right (T.foldl' go 0 h, t)
Expand All @@ -48,25 +48,25 @@ decimal txt
-- --
-- This function does not handle leading sign characters. If you need -- This function does not handle leading sign characters. If you need
-- to handle signed input, use @'signed' 'hexadecimal'@. -- to handle signed input, use @'signed' 'hexadecimal'@.
hexadecimal :: Integral a => Lexer a hexadecimal :: Integral a => Reader a
{-# SPECIALIZE hex :: Lexer Int #-} {-# SPECIALIZE hex :: Reader Int #-}
{-# SPECIALIZE hex :: Lexer Integer #-} {-# SPECIALIZE hex :: Reader Integer #-}
hexadecimal txt hexadecimal txt
| T.toLower h == "0x" = hex t | T.toLower h == "0x" = hex t
| otherwise = hex txt | otherwise = hex txt
where (h,t) = T.splitAt 2 txt where (h,t) = T.splitAt 2 txt


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


-- | Read a rational number. -- | Read a rational number.
-- --
-- This function accepts an optional leading sign character. -- This function accepts an optional leading sign character.
rational :: RealFloat a => Lexer a rational :: RealFloat a => Reader a
{-# SPECIALIZE rational :: Lexer Double #-} {-# SPECIALIZE rational :: Reader Double #-}
rational = floaty $ \real frac fracDenom -> fromRational $ rational = floaty $ \real frac fracDenom -> fromRational $
real % 1 + frac % fracDenom real % 1 + frac % fracDenom


Expand All @@ -82,14 +82,14 @@ rational = floaty $ \real frac fracDenom -> fromRational $
-- results, but for the remaining 5.8%, this function loses precision -- results, but for the remaining 5.8%, this function loses precision
-- around the 15th decimal place. For 0.001% of numbers, this -- around the 15th decimal place. For 0.001% of numbers, this
-- function will lose precision at the 13th or 14th decimal place. -- function will lose precision at the 13th or 14th decimal place.
double :: Lexer Double double :: Reader Double
double = floaty $ \real frac fracDenom -> double = floaty $ \real frac fracDenom ->
fromIntegral real + fromIntegral real +
fromIntegral frac / fromIntegral fracDenom fromIntegral frac / fromIntegral fracDenom


hex :: Integral a => Lexer a hex :: Integral a => Reader a
{-# SPECIALIZE hex :: Lexer Int #-} {-# SPECIALIZE hex :: Reader Int #-}
{-# SPECIALIZE hex :: Lexer Integer #-} {-# SPECIALIZE hex :: Reader Integer #-}
hex txt hex txt
| T.null h = Left "no digits in input" | T.null h = Left "no digits in input"
| otherwise = Right (T.foldl' go 0 h, t) | otherwise = Right (T.foldl' go 0 h, t)
Expand Down Expand Up @@ -135,7 +135,7 @@ char p = P $ \t -> case T.uncons t of


data T = T !Integer !Int data T = T !Integer !Int


floaty :: RealFloat a => (Integer -> Integer -> Integer -> a) -> Lexer a floaty :: RealFloat a => (Integer -> Integer -> Integer -> a) -> Reader a
{-# INLINE floaty #-} {-# INLINE floaty #-}
floaty f = runP $ do floaty f = runP $ do
real <- signa (P decimal) real <- signa (P decimal)
Expand Down
12 changes: 6 additions & 6 deletions tests/benchmarks/ReadNumbers.hs
Original file line number Original file line Diff line number Diff line change
Expand Up @@ -2,20 +2,20 @@
import Debug.Trace import Debug.Trace
import Control.Monad import Control.Monad
import Data.List import Data.List
import qualified Data.Text.Lex as T import qualified Data.Text.Read as T
import qualified Data.Text.IO as T import qualified Data.Text.IO as T
import qualified Data.Text as T import qualified Data.Text as T
import System.Environment import System.Environment


dec = T.signed T.decimal :: T.Lexer Int dec = T.signed T.decimal :: T.Reader Int


hex = T.signed T.hexadecimal :: T.Lexer Int hex = T.signed T.hexadecimal :: T.Reader Int


double = T.double :: T.Lexer Double double = T.double :: T.Reader Double


def = double def = double


read1 :: Num a => T.Lexer a -> T.Text -> a read1 :: Num a => T.Reader a -> T.Text -> a
read1 reader = foldl' go 0 . T.lines read1 reader = foldl' go 0 . T.lines
where go z t = case reader t of where go z t = case reader t of
Left err -> error err Left err -> error err
Expand All @@ -33,7 +33,7 @@ paranoid = foldr go [] . T.lines
then abs ((a-b)/a) : xs then abs ((a-b)/a) : xs
else xs else xs


read2 :: Num a => T.Lexer a -> T.Text -> a read2 :: Num a => T.Reader a -> T.Text -> a
read2 reader = go 0 read2 reader = go 0
where where
go !i t go !i t
Expand Down
2 changes: 1 addition & 1 deletion text.cabal
Original file line number Original file line Diff line number Diff line change
Expand Up @@ -74,11 +74,11 @@ library
Data.Text.Encoding.Error Data.Text.Encoding.Error
Data.Text.Foreign Data.Text.Foreign
Data.Text.IO Data.Text.IO
Data.Text.Lex
Data.Text.Lazy Data.Text.Lazy
Data.Text.Lazy.Builder Data.Text.Lazy.Builder
Data.Text.Lazy.Encoding Data.Text.Lazy.Encoding
Data.Text.Lazy.IO Data.Text.Lazy.IO
Data.Text.Read
other-modules: other-modules:
Data.Text.Array Data.Text.Array
Data.Text.Encoding.Fusion Data.Text.Encoding.Fusion
Expand Down

0 comments on commit b18bfc1

Please sign in to comment.