{-# LANGUAGE DeriveDataTypeable #-}
module GHC.Types.SourceText
   ( SourceText (..)
   , pprWithSourceText
   
   , IntegralLit(..)
   , FractionalLit(..)
   , StringLiteral(..)
   , negateIntegralLit
   , negateFractionalLit
   , mkIntegralLit
   , mkTHFractionalLit, rationalFromFractionalLit
   , integralFractionalLit, mkSourceFractionalLit
   , FractionalExponentBase(..)
   
   , fractionalLitFromRational
   , mkFractionalLit
   )
where
import GHC.Prelude
import GHC.Data.FastString
import GHC.Utils.Outputable
import GHC.Utils.Binary
import GHC.Utils.Panic
import Data.Function (on)
import Data.Data
import GHC.Real ( Ratio(..) )
import GHC.Types.SrcLoc
 
data SourceText
   = SourceText String
   | NoSourceText
      
      
      
   deriving (Typeable SourceText
DataType
Constr
Typeable SourceText
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> SourceText -> c SourceText)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SourceText)
-> (SourceText -> Constr)
-> (SourceText -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SourceText))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SourceText))
-> ((forall b. Data b => b -> b) -> SourceText -> SourceText)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SourceText -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SourceText -> r)
-> (forall u. (forall d. Data d => d -> u) -> SourceText -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> SourceText -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> SourceText -> m SourceText)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SourceText -> m SourceText)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SourceText -> m SourceText)
-> Data SourceText
SourceText -> DataType
SourceText -> Constr
(forall b. Data b => b -> b) -> SourceText -> SourceText
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceText -> c SourceText
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceText
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SourceText -> u
forall u. (forall d. Data d => d -> u) -> SourceText -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceText -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceText -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourceText -> m SourceText
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceText -> m SourceText
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceText
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceText -> c SourceText
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourceText)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText)
$cNoSourceText :: Constr
$cSourceText :: Constr
$tSourceText :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SourceText -> m SourceText
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceText -> m SourceText
gmapMp :: (forall d. Data d => d -> m d) -> SourceText -> m SourceText
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SourceText -> m SourceText
gmapM :: (forall d. Data d => d -> m d) -> SourceText -> m SourceText
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SourceText -> m SourceText
gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceText -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SourceText -> u
gmapQ :: (forall d. Data d => d -> u) -> SourceText -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SourceText -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceText -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SourceText -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceText -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SourceText -> r
gmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText
$cgmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SourceText)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SourceText)
dataTypeOf :: SourceText -> DataType
$cdataTypeOf :: SourceText -> DataType
toConstr :: SourceText -> Constr
$ctoConstr :: SourceText -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceText
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SourceText
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceText -> c SourceText
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SourceText -> c SourceText
$cp1Data :: Typeable SourceText
Data, Int -> SourceText -> ShowS
[SourceText] -> ShowS
SourceText -> String
(Int -> SourceText -> ShowS)
-> (SourceText -> String)
-> ([SourceText] -> ShowS)
-> Show SourceText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceText] -> ShowS
$cshowList :: [SourceText] -> ShowS
show :: SourceText -> String
$cshow :: SourceText -> String
showsPrec :: Int -> SourceText -> ShowS
$cshowsPrec :: Int -> SourceText -> ShowS
Show, SourceText -> SourceText -> Bool
(SourceText -> SourceText -> Bool)
-> (SourceText -> SourceText -> Bool) -> Eq SourceText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceText -> SourceText -> Bool
$c/= :: SourceText -> SourceText -> Bool
== :: SourceText -> SourceText -> Bool
$c== :: SourceText -> SourceText -> Bool
Eq )
instance Outputable SourceText where
  ppr :: SourceText -> SDoc
ppr (SourceText String
s) = String -> SDoc
text String
"SourceText" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
s
  ppr SourceText
NoSourceText   = String -> SDoc
text String
"NoSourceText"
instance Binary SourceText where
  put_ :: BinHandle -> SourceText -> IO ()
put_ BinHandle
bh SourceText
NoSourceText = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
  put_ BinHandle
bh (SourceText String
s) = do
        BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
        BinHandle -> String -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh String
s
  get :: BinHandle -> IO SourceText
get BinHandle
bh = do
    Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
    case Word8
h of
      Word8
0 -> SourceText -> IO SourceText
forall (m :: * -> *) a. Monad m => a -> m a
return SourceText
NoSourceText
      Word8
1 -> do
        String
s <- BinHandle -> IO String
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
        SourceText -> IO SourceText
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> SourceText
SourceText String
s)
      Word8
_ -> String -> IO SourceText
forall a. String -> a
panic (String -> IO SourceText) -> String -> IO SourceText
forall a b. (a -> b) -> a -> b
$ String
"Binary SourceText:" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
h
pprWithSourceText :: SourceText -> SDoc -> SDoc
pprWithSourceText :: SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
NoSourceText     SDoc
d = SDoc
d
pprWithSourceText (SourceText String
src) SDoc
_ = String -> SDoc
text String
src
data IntegralLit = IL
   { IntegralLit -> SourceText
il_text  :: SourceText
   , IntegralLit -> Bool
il_neg   :: Bool 
   , IntegralLit -> Integer
il_value :: Integer
   }
   deriving (Typeable IntegralLit
DataType
Constr
Typeable IntegralLit
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> IntegralLit -> c IntegralLit)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c IntegralLit)
-> (IntegralLit -> Constr)
-> (IntegralLit -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c IntegralLit))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c IntegralLit))
-> ((forall b. Data b => b -> b) -> IntegralLit -> IntegralLit)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> IntegralLit -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> IntegralLit -> r)
-> (forall u. (forall d. Data d => d -> u) -> IntegralLit -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> IntegralLit -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit)
-> Data IntegralLit
IntegralLit -> DataType
IntegralLit -> Constr
(forall b. Data b => b -> b) -> IntegralLit -> IntegralLit
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IntegralLit -> c IntegralLit
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IntegralLit
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IntegralLit -> u
forall u. (forall d. Data d => d -> u) -> IntegralLit -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IntegralLit -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IntegralLit -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IntegralLit
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IntegralLit -> c IntegralLit
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IntegralLit)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IntegralLit)
$cIL :: Constr
$tIntegralLit :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
gmapMp :: (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
gmapM :: (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit
gmapQi :: Int -> (forall d. Data d => d -> u) -> IntegralLit -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IntegralLit -> u
gmapQ :: (forall d. Data d => d -> u) -> IntegralLit -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IntegralLit -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IntegralLit -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IntegralLit -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IntegralLit -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IntegralLit -> r
gmapT :: (forall b. Data b => b -> b) -> IntegralLit -> IntegralLit
$cgmapT :: (forall b. Data b => b -> b) -> IntegralLit -> IntegralLit
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IntegralLit)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IntegralLit)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c IntegralLit)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IntegralLit)
dataTypeOf :: IntegralLit -> DataType
$cdataTypeOf :: IntegralLit -> DataType
toConstr :: IntegralLit -> Constr
$ctoConstr :: IntegralLit -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IntegralLit
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IntegralLit
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IntegralLit -> c IntegralLit
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IntegralLit -> c IntegralLit
$cp1Data :: Typeable IntegralLit
Data, Int -> IntegralLit -> ShowS
[IntegralLit] -> ShowS
IntegralLit -> String
(Int -> IntegralLit -> ShowS)
-> (IntegralLit -> String)
-> ([IntegralLit] -> ShowS)
-> Show IntegralLit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IntegralLit] -> ShowS
$cshowList :: [IntegralLit] -> ShowS
show :: IntegralLit -> String
$cshow :: IntegralLit -> String
showsPrec :: Int -> IntegralLit -> ShowS
$cshowsPrec :: Int -> IntegralLit -> ShowS
Show)
mkIntegralLit :: Integral a => a -> IntegralLit
mkIntegralLit :: a -> IntegralLit
mkIntegralLit a
i = IL :: SourceText -> Bool -> Integer -> IntegralLit
IL { il_text :: SourceText
il_text = String -> SourceText
SourceText (Integer -> String
forall a. Show a => a -> String
show Integer
i_integer)
                     , il_neg :: Bool
il_neg = a
i a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0
                     , il_value :: Integer
il_value = Integer
i_integer }
  where
    i_integer :: Integer
    i_integer :: Integer
i_integer = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
i
negateIntegralLit :: IntegralLit -> IntegralLit
negateIntegralLit :: IntegralLit -> IntegralLit
negateIntegralLit (IL SourceText
text Bool
neg Integer
value)
  = case SourceText
text of
      SourceText (Char
'-':String
src) -> SourceText -> Bool -> Integer -> IntegralLit
IL (String -> SourceText
SourceText String
src)       Bool
False    (Integer -> Integer
forall a. Num a => a -> a
negate Integer
value)
      SourceText      String
src  -> SourceText -> Bool -> Integer -> IntegralLit
IL (String -> SourceText
SourceText (Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:String
src)) Bool
True     (Integer -> Integer
forall a. Num a => a -> a
negate Integer
value)
      SourceText
NoSourceText         -> SourceText -> Bool -> Integer -> IntegralLit
IL SourceText
NoSourceText          (Bool -> Bool
not Bool
neg) (Integer -> Integer
forall a. Num a => a -> a
negate Integer
value)
data FractionalLit = FL
    { FractionalLit -> SourceText
fl_text :: SourceText     
    , FractionalLit -> Bool
fl_neg :: Bool                        
    , FractionalLit -> Rational
fl_signi :: Rational                  
    , FractionalLit -> Integer
fl_exp :: Integer                     
    , FractionalLit -> FractionalExponentBase
fl_exp_base :: FractionalExponentBase 
    }
    deriving (Typeable FractionalLit
DataType
Constr
Typeable FractionalLit
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> FractionalLit -> c FractionalLit)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c FractionalLit)
-> (FractionalLit -> Constr)
-> (FractionalLit -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c FractionalLit))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c FractionalLit))
-> ((forall b. Data b => b -> b) -> FractionalLit -> FractionalLit)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> FractionalLit -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> FractionalLit -> r)
-> (forall u. (forall d. Data d => d -> u) -> FractionalLit -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> FractionalLit -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit)
-> Data FractionalLit
FractionalLit -> DataType
FractionalLit -> Constr
(forall b. Data b => b -> b) -> FractionalLit -> FractionalLit
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionalLit -> c FractionalLit
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalLit
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FractionalLit -> u
forall u. (forall d. Data d => d -> u) -> FractionalLit -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionalLit -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionalLit -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalLit
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionalLit -> c FractionalLit
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionalLit)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionalLit)
$cFL :: Constr
$tFractionalLit :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
gmapMp :: (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
gmapM :: (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit
gmapQi :: Int -> (forall d. Data d => d -> u) -> FractionalLit -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FractionalLit -> u
gmapQ :: (forall d. Data d => d -> u) -> FractionalLit -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FractionalLit -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionalLit -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FractionalLit -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionalLit -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FractionalLit -> r
gmapT :: (forall b. Data b => b -> b) -> FractionalLit -> FractionalLit
$cgmapT :: (forall b. Data b => b -> b) -> FractionalLit -> FractionalLit
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionalLit)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionalLit)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FractionalLit)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionalLit)
dataTypeOf :: FractionalLit -> DataType
$cdataTypeOf :: FractionalLit -> DataType
toConstr :: FractionalLit -> Constr
$ctoConstr :: FractionalLit -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalLit
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalLit
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionalLit -> c FractionalLit
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FractionalLit -> c FractionalLit
$cp1Data :: Typeable FractionalLit
Data, Int -> FractionalLit -> ShowS
[FractionalLit] -> ShowS
FractionalLit -> String
(Int -> FractionalLit -> ShowS)
-> (FractionalLit -> String)
-> ([FractionalLit] -> ShowS)
-> Show FractionalLit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FractionalLit] -> ShowS
$cshowList :: [FractionalLit] -> ShowS
show :: FractionalLit -> String
$cshow :: FractionalLit -> String
showsPrec :: Int -> FractionalLit -> ShowS
$cshowsPrec :: Int -> FractionalLit -> ShowS
Show)
  
data FractionalExponentBase
  = Base2 
  | Base10
  deriving (FractionalExponentBase -> FractionalExponentBase -> Bool
(FractionalExponentBase -> FractionalExponentBase -> Bool)
-> (FractionalExponentBase -> FractionalExponentBase -> Bool)
-> Eq FractionalExponentBase
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FractionalExponentBase -> FractionalExponentBase -> Bool
$c/= :: FractionalExponentBase -> FractionalExponentBase -> Bool
== :: FractionalExponentBase -> FractionalExponentBase -> Bool
$c== :: FractionalExponentBase -> FractionalExponentBase -> Bool
Eq, Eq FractionalExponentBase
Eq FractionalExponentBase
-> (FractionalExponentBase -> FractionalExponentBase -> Ordering)
-> (FractionalExponentBase -> FractionalExponentBase -> Bool)
-> (FractionalExponentBase -> FractionalExponentBase -> Bool)
-> (FractionalExponentBase -> FractionalExponentBase -> Bool)
-> (FractionalExponentBase -> FractionalExponentBase -> Bool)
-> (FractionalExponentBase
    -> FractionalExponentBase -> FractionalExponentBase)
-> (FractionalExponentBase
    -> FractionalExponentBase -> FractionalExponentBase)
-> Ord FractionalExponentBase
FractionalExponentBase -> FractionalExponentBase -> Bool
FractionalExponentBase -> FractionalExponentBase -> Ordering
FractionalExponentBase
-> FractionalExponentBase -> FractionalExponentBase
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FractionalExponentBase
-> FractionalExponentBase -> FractionalExponentBase
$cmin :: FractionalExponentBase
-> FractionalExponentBase -> FractionalExponentBase
max :: FractionalExponentBase
-> FractionalExponentBase -> FractionalExponentBase
$cmax :: FractionalExponentBase
-> FractionalExponentBase -> FractionalExponentBase
>= :: FractionalExponentBase -> FractionalExponentBase -> Bool
$c>= :: FractionalExponentBase -> FractionalExponentBase -> Bool
> :: FractionalExponentBase -> FractionalExponentBase -> Bool
$c> :: FractionalExponentBase -> FractionalExponentBase -> Bool
<= :: FractionalExponentBase -> FractionalExponentBase -> Bool
$c<= :: FractionalExponentBase -> FractionalExponentBase -> Bool
< :: FractionalExponentBase -> FractionalExponentBase -> Bool
$c< :: FractionalExponentBase -> FractionalExponentBase -> Bool
compare :: FractionalExponentBase -> FractionalExponentBase -> Ordering
$ccompare :: FractionalExponentBase -> FractionalExponentBase -> Ordering
$cp1Ord :: Eq FractionalExponentBase
Ord, Typeable FractionalExponentBase
DataType
Constr
Typeable FractionalExponentBase
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> FractionalExponentBase
    -> c FractionalExponentBase)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c FractionalExponentBase)
-> (FractionalExponentBase -> Constr)
-> (FractionalExponentBase -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c FractionalExponentBase))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c FractionalExponentBase))
-> ((forall b. Data b => b -> b)
    -> FractionalExponentBase -> FractionalExponentBase)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> FractionalExponentBase
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> FractionalExponentBase
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> FractionalExponentBase -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> FractionalExponentBase -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> FractionalExponentBase -> m FractionalExponentBase)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> FractionalExponentBase -> m FractionalExponentBase)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> FractionalExponentBase -> m FractionalExponentBase)
-> Data FractionalExponentBase
FractionalExponentBase -> DataType
FractionalExponentBase -> Constr
(forall b. Data b => b -> b)
-> FractionalExponentBase -> FractionalExponentBase
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FractionalExponentBase
-> c FractionalExponentBase
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalExponentBase
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> FractionalExponentBase -> u
forall u.
(forall d. Data d => d -> u) -> FractionalExponentBase -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FractionalExponentBase
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FractionalExponentBase
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalExponentBase
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FractionalExponentBase
-> c FractionalExponentBase
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionalExponentBase)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionalExponentBase)
$cBase10 :: Constr
$cBase2 :: Constr
$tFractionalExponentBase :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
gmapMp :: (forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
gmapM :: (forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FractionalExponentBase -> m FractionalExponentBase
gmapQi :: Int -> (forall d. Data d => d -> u) -> FractionalExponentBase -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FractionalExponentBase -> u
gmapQ :: (forall d. Data d => d -> u) -> FractionalExponentBase -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> FractionalExponentBase -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FractionalExponentBase
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> FractionalExponentBase
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FractionalExponentBase
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> FractionalExponentBase
-> r
gmapT :: (forall b. Data b => b -> b)
-> FractionalExponentBase -> FractionalExponentBase
$cgmapT :: (forall b. Data b => b -> b)
-> FractionalExponentBase -> FractionalExponentBase
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionalExponentBase)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FractionalExponentBase)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FractionalExponentBase)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FractionalExponentBase)
dataTypeOf :: FractionalExponentBase -> DataType
$cdataTypeOf :: FractionalExponentBase -> DataType
toConstr :: FractionalExponentBase -> Constr
$ctoConstr :: FractionalExponentBase -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalExponentBase
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FractionalExponentBase
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FractionalExponentBase
-> c FractionalExponentBase
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> FractionalExponentBase
-> c FractionalExponentBase
$cp1Data :: Typeable FractionalExponentBase
Data, Int -> FractionalExponentBase -> ShowS
[FractionalExponentBase] -> ShowS
FractionalExponentBase -> String
(Int -> FractionalExponentBase -> ShowS)
-> (FractionalExponentBase -> String)
-> ([FractionalExponentBase] -> ShowS)
-> Show FractionalExponentBase
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FractionalExponentBase] -> ShowS
$cshowList :: [FractionalExponentBase] -> ShowS
show :: FractionalExponentBase -> String
$cshow :: FractionalExponentBase -> String
showsPrec :: Int -> FractionalExponentBase -> ShowS
$cshowsPrec :: Int -> FractionalExponentBase -> ShowS
Show)
mkFractionalLit :: SourceText -> Bool -> Rational -> Integer -> FractionalExponentBase
                -> FractionalLit
mkFractionalLit :: SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
mkFractionalLit = SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL
mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase Rational
i Integer
e FractionalExponentBase
feb = Rational
i Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Rational
eb Rational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Integer
e)
  where eb :: Rational
eb = case FractionalExponentBase
feb of FractionalExponentBase
Base2 -> Rational
2 ; FractionalExponentBase
Base10 -> Rational
10
fractionalLitFromRational :: Rational -> FractionalLit
fractionalLitFromRational :: Rational -> FractionalLit
fractionalLitFromRational Rational
r =  FL :: SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL { fl_text :: SourceText
fl_text = SourceText
NoSourceText
                           , fl_neg :: Bool
fl_neg = Rational
r Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
< Rational
0
                           , fl_signi :: Rational
fl_signi = Rational
r
                           , fl_exp :: Integer
fl_exp = Integer
0
                           , fl_exp_base :: FractionalExponentBase
fl_exp_base = FractionalExponentBase
Base10 }
rationalFromFractionalLit :: FractionalLit -> Rational
rationalFromFractionalLit :: FractionalLit -> Rational
rationalFromFractionalLit (FL SourceText
_ Bool
_ Rational
i Integer
e FractionalExponentBase
expBase) =
  Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase Rational
i Integer
e FractionalExponentBase
expBase
mkTHFractionalLit :: Rational -> FractionalLit
mkTHFractionalLit :: Rational -> FractionalLit
mkTHFractionalLit Rational
r =  FL :: SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL { fl_text :: SourceText
fl_text = String -> SourceText
SourceText (Double -> String
forall a. Show a => a -> String
show (Rational -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Rational
r::Double))
                             
                             
                             
                             
                             
                             
                             
                           , fl_neg :: Bool
fl_neg = Rational
r Rational -> Rational -> Bool
forall a. Ord a => a -> a -> Bool
< Rational
0
                           , fl_signi :: Rational
fl_signi = Rational
r
                           , fl_exp :: Integer
fl_exp = Integer
0
                           , fl_exp_base :: FractionalExponentBase
fl_exp_base = FractionalExponentBase
Base10 }
negateFractionalLit :: FractionalLit -> FractionalLit
negateFractionalLit :: FractionalLit -> FractionalLit
negateFractionalLit (FL SourceText
text Bool
neg Rational
i Integer
e FractionalExponentBase
eb)
  = case SourceText
text of
      SourceText (Char
'-':String
src) -> SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL (String -> SourceText
SourceText String
src)       Bool
False (Rational -> Rational
forall a. Num a => a -> a
negate Rational
i) Integer
e FractionalExponentBase
eb
      SourceText      String
src  -> SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL (String -> SourceText
SourceText (Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:String
src)) Bool
True  (Rational -> Rational
forall a. Num a => a -> a
negate Rational
i) Integer
e FractionalExponentBase
eb
      SourceText
NoSourceText         -> SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL SourceText
NoSourceText (Bool -> Bool
not Bool
neg) (Rational -> Rational
forall a. Num a => a -> a
negate Rational
i) Integer
e FractionalExponentBase
eb
integralFractionalLit :: Bool -> Integer -> FractionalLit
integralFractionalLit :: Bool -> Integer -> FractionalLit
integralFractionalLit Bool
neg Integer
i = FL :: SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL { fl_text :: SourceText
fl_text = String -> SourceText
SourceText (Integer -> String
forall a. Show a => a -> String
show Integer
i)
                                 , fl_neg :: Bool
fl_neg = Bool
neg
                                 , fl_signi :: Rational
fl_signi = Integer
i Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
                                 , fl_exp :: Integer
fl_exp = Integer
0
                                 , fl_exp_base :: FractionalExponentBase
fl_exp_base = FractionalExponentBase
Base10 }
mkSourceFractionalLit :: String -> Bool -> Integer -> Integer
                      -> FractionalExponentBase
                      -> FractionalLit
mkSourceFractionalLit :: String
-> Bool
-> Integer
-> Integer
-> FractionalExponentBase
-> FractionalLit
mkSourceFractionalLit !String
str !Bool
b !Integer
r !Integer
i !FractionalExponentBase
ff = SourceText
-> Bool
-> Rational
-> Integer
-> FractionalExponentBase
-> FractionalLit
FL (String -> SourceText
SourceText String
str) Bool
b (Integer
r Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1) Integer
i FractionalExponentBase
ff
instance Eq IntegralLit where
  == :: IntegralLit -> IntegralLit -> Bool
(==) = Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Integer -> Integer -> Bool)
-> (IntegralLit -> Integer) -> IntegralLit -> IntegralLit -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` IntegralLit -> Integer
il_value
instance Ord IntegralLit where
  compare :: IntegralLit -> IntegralLit -> Ordering
compare = Integer -> Integer -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Integer -> Integer -> Ordering)
-> (IntegralLit -> Integer)
-> IntegralLit
-> IntegralLit
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` IntegralLit -> Integer
il_value
instance Outputable IntegralLit where
  ppr :: IntegralLit -> SDoc
ppr (IL (SourceText String
src) Bool
_ Integer
_) = String -> SDoc
text String
src
  ppr (IL SourceText
NoSourceText Bool
_ Integer
value) = String -> SDoc
text (Integer -> String
forall a. Show a => a -> String
show Integer
value)
compareFractionalLit :: FractionalLit -> FractionalLit -> Ordering
compareFractionalLit :: FractionalLit -> FractionalLit -> Ordering
compareFractionalLit FractionalLit
fl1 FractionalLit
fl2
  | FractionalLit -> Integer
fl_exp FractionalLit
fl1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
100 Bool -> Bool -> Bool
&& FractionalLit -> Integer
fl_exp FractionalLit
fl2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
100 Bool -> Bool -> Bool
&& FractionalLit -> Integer
fl_exp FractionalLit
fl1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= -Integer
100 Bool -> Bool -> Bool
&& FractionalLit -> Integer
fl_exp FractionalLit
fl2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= -Integer
100
    = FractionalLit -> Rational
rationalFromFractionalLit FractionalLit
fl1 Rational -> Rational -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` FractionalLit -> Rational
rationalFromFractionalLit FractionalLit
fl2
  | Bool
otherwise = ((Rational, Integer, FractionalExponentBase)
-> (Rational, Integer, FractionalExponentBase) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ((Rational, Integer, FractionalExponentBase)
 -> (Rational, Integer, FractionalExponentBase) -> Ordering)
-> (FractionalLit -> (Rational, Integer, FractionalExponentBase))
-> FractionalLit
-> FractionalLit
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (\FractionalLit
x -> (FractionalLit -> Rational
fl_signi FractionalLit
x, FractionalLit -> Integer
fl_exp FractionalLit
x, FractionalLit -> FractionalExponentBase
fl_exp_base FractionalLit
x))) FractionalLit
fl1 FractionalLit
fl2
instance Eq FractionalLit where
  == :: FractionalLit -> FractionalLit -> Bool
(==) FractionalLit
fl1 FractionalLit
fl2 = case FractionalLit -> FractionalLit -> Ordering
forall a. Ord a => a -> a -> Ordering
compare FractionalLit
fl1 FractionalLit
fl2 of
          Ordering
EQ -> Bool
True
          Ordering
_  -> Bool
False
instance Ord FractionalLit where
  compare :: FractionalLit -> FractionalLit -> Ordering
compare = FractionalLit -> FractionalLit -> Ordering
compareFractionalLit
instance Outputable FractionalLit where
  ppr :: FractionalLit -> SDoc
ppr (fl :: FractionalLit
fl@(FL {})) =
    SourceText -> SDoc -> SDoc
pprWithSourceText (FractionalLit -> SourceText
fl_text FractionalLit
fl) (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
      Rational -> SDoc
rational (Rational -> SDoc) -> Rational -> SDoc
forall a b. (a -> b) -> a -> b
$ Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase (FractionalLit -> Rational
fl_signi FractionalLit
fl) (FractionalLit -> Integer
fl_exp FractionalLit
fl) (FractionalLit -> FractionalExponentBase
fl_exp_base FractionalLit
fl)
data StringLiteral = StringLiteral
                       { StringLiteral -> SourceText
sl_st :: SourceText, 
                                              
                         StringLiteral -> FastString
sl_fs :: FastString, 
                         StringLiteral -> Maybe RealSrcSpan
sl_tc :: Maybe RealSrcSpan 
                                                    
                                                    
                       
                       
                       
                       
                       
                       
                       } deriving Typeable StringLiteral
DataType
Constr
Typeable StringLiteral
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> StringLiteral -> c StringLiteral)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c StringLiteral)
-> (StringLiteral -> Constr)
-> (StringLiteral -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c StringLiteral))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c StringLiteral))
-> ((forall b. Data b => b -> b) -> StringLiteral -> StringLiteral)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> StringLiteral -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> StringLiteral -> r)
-> (forall u. (forall d. Data d => d -> u) -> StringLiteral -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> StringLiteral -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral)
-> Data StringLiteral
StringLiteral -> DataType
StringLiteral -> Constr
(forall b. Data b => b -> b) -> StringLiteral -> StringLiteral
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StringLiteral -> c StringLiteral
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c StringLiteral
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> StringLiteral -> u
forall u. (forall d. Data d => d -> u) -> StringLiteral -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StringLiteral -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StringLiteral -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c StringLiteral
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StringLiteral -> c StringLiteral
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c StringLiteral)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c StringLiteral)
$cStringLiteral :: Constr
$tStringLiteral :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
gmapMp :: (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
gmapM :: (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral
gmapQi :: Int -> (forall d. Data d => d -> u) -> StringLiteral -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> StringLiteral -> u
gmapQ :: (forall d. Data d => d -> u) -> StringLiteral -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> StringLiteral -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StringLiteral -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> StringLiteral -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StringLiteral -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> StringLiteral -> r
gmapT :: (forall b. Data b => b -> b) -> StringLiteral -> StringLiteral
$cgmapT :: (forall b. Data b => b -> b) -> StringLiteral -> StringLiteral
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c StringLiteral)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c StringLiteral)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c StringLiteral)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c StringLiteral)
dataTypeOf :: StringLiteral -> DataType
$cdataTypeOf :: StringLiteral -> DataType
toConstr :: StringLiteral -> Constr
$ctoConstr :: StringLiteral -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c StringLiteral
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c StringLiteral
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StringLiteral -> c StringLiteral
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> StringLiteral -> c StringLiteral
$cp1Data :: Typeable StringLiteral
Data
instance Eq StringLiteral where
  (StringLiteral SourceText
_ FastString
a Maybe RealSrcSpan
_) == :: StringLiteral -> StringLiteral -> Bool
== (StringLiteral SourceText
_ FastString
b Maybe RealSrcSpan
_) = FastString
a FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== FastString
b
instance Outputable StringLiteral where
  ppr :: StringLiteral -> SDoc
ppr StringLiteral
sl = SourceText -> SDoc -> SDoc
pprWithSourceText (StringLiteral -> SourceText
sl_st StringLiteral
sl) (FastString -> SDoc
ftext (FastString -> SDoc) -> FastString -> SDoc
forall a b. (a -> b) -> a -> b
$ StringLiteral -> FastString
sl_fs StringLiteral
sl)
instance Binary StringLiteral where
  put_ :: BinHandle -> StringLiteral -> IO ()
put_ BinHandle
bh (StringLiteral SourceText
st FastString
fs Maybe RealSrcSpan
_) = do
            BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
st
            BinHandle -> FastString -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FastString
fs
  get :: BinHandle -> IO StringLiteral
get BinHandle
bh = do
            SourceText
st <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            FastString
fs <- BinHandle -> IO FastString
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
            StringLiteral -> IO StringLiteral
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> FastString -> Maybe RealSrcSpan -> StringLiteral
StringLiteral SourceText
st FastString
fs Maybe RealSrcSpan
forall a. Maybe a
Nothing)