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 (Data, Show, Eq )
instance Outputable SourceText where
ppr (SourceText s) = text "SourceText" <+> text s
ppr NoSourceText = text "NoSourceText"
instance Binary SourceText where
put_ bh NoSourceText = putByte bh 0
put_ bh (SourceText s) = do
putByte bh 1
put_ bh s
get bh = do
h <- getByte bh
case h of
0 -> return NoSourceText
1 -> do
s <- get bh
return (SourceText s)
_ -> panic $ "Binary SourceText:" ++ show h
pprWithSourceText :: SourceText -> SDoc -> SDoc
pprWithSourceText NoSourceText d = d
pprWithSourceText (SourceText src) _ = text src
data IntegralLit = IL
{ il_text :: SourceText
, il_neg :: Bool
, il_value :: Integer
}
deriving (Data, Show)
mkIntegralLit :: Integral a => a -> IntegralLit
mkIntegralLit i = IL { il_text = SourceText (show i_integer)
, il_neg = i < 0
, il_value = i_integer }
where
i_integer :: Integer
i_integer = toInteger i
negateIntegralLit :: IntegralLit -> IntegralLit
negateIntegralLit (IL text neg value)
= case text of
SourceText ('-':src) -> IL (SourceText src) False (negate value)
SourceText src -> IL (SourceText ('-':src)) True (negate value)
NoSourceText -> IL NoSourceText (not neg) (negate value)
data FractionalLit = FL
{ fl_text :: SourceText
, fl_neg :: Bool
, fl_signi :: Rational
, fl_exp :: Integer
, fl_exp_base :: FractionalExponentBase
}
deriving (Data, Show)
data FractionalExponentBase
= Base2
| Base10
deriving (Eq, Ord, Data, Show)
mkFractionalLit :: SourceText -> Bool -> Rational -> Integer -> FractionalExponentBase
-> FractionalLit
mkFractionalLit = FL
mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase i e feb = i * (eb ^^ e)
where eb = case feb of Base2 -> 2 ; Base10 -> 10
fractionalLitFromRational :: Rational -> FractionalLit
fractionalLitFromRational r = FL { fl_text = NoSourceText
, fl_neg = r < 0
, fl_signi = r
, fl_exp = 0
, fl_exp_base = Base10 }
rationalFromFractionalLit :: FractionalLit -> Rational
rationalFromFractionalLit (FL _ _ i e expBase) =
mkRationalWithExponentBase i e expBase
mkTHFractionalLit :: Rational -> FractionalLit
mkTHFractionalLit r = FL { fl_text = SourceText (show (realToFrac r::Double))
, fl_neg = r < 0
, fl_signi = r
, fl_exp = 0
, fl_exp_base = Base10 }
negateFractionalLit :: FractionalLit -> FractionalLit
negateFractionalLit (FL text neg i e eb)
= case text of
SourceText ('-':src) -> FL (SourceText src) False i e eb
SourceText src -> FL (SourceText ('-':src)) True i e eb
NoSourceText -> FL NoSourceText (not neg) (negate i) e eb
integralFractionalLit :: Bool -> Integer -> FractionalLit
integralFractionalLit neg i = FL { fl_text = SourceText (show i)
, fl_neg = neg
, fl_signi = i :% 1
, fl_exp = 0
, fl_exp_base = Base10 }
mkSourceFractionalLit :: String -> Bool -> Integer -> Integer
-> FractionalExponentBase
-> FractionalLit
mkSourceFractionalLit !str !b !r !i !ff = FL (SourceText str) b (r :% 1) i ff
instance Eq IntegralLit where
(==) = (==) `on` il_value
instance Ord IntegralLit where
compare = compare `on` il_value
instance Outputable IntegralLit where
ppr (IL (SourceText src) _ _) = text src
ppr (IL NoSourceText _ value) = text (show value)
compareFractionalLit :: FractionalLit -> FractionalLit -> Ordering
compareFractionalLit fl1 fl2
| fl_exp fl1 < 100 && fl_exp fl2 < 100 && fl_exp fl1 >= 100 && fl_exp fl2 >= 100
= rationalFromFractionalLit fl1 `compare` rationalFromFractionalLit fl2
| otherwise = (compare `on` (\x -> (fl_signi x, fl_exp x, fl_exp_base x))) fl1 fl2
instance Eq FractionalLit where
(==) fl1 fl2 = case compare fl1 fl2 of
EQ -> True
_ -> False
instance Ord FractionalLit where
compare = compareFractionalLit
instance Outputable FractionalLit where
ppr (fl@(FL {})) =
pprWithSourceText (fl_text fl) $
rational $ mkRationalWithExponentBase (fl_signi fl) (fl_exp fl) (fl_exp_base fl)
data StringLiteral = StringLiteral
{ sl_st :: SourceText,
sl_fs :: FastString,
sl_tc :: Maybe RealSrcSpan
} deriving Data
instance Eq StringLiteral where
(StringLiteral _ a _) == (StringLiteral _ b _) = a == b
instance Outputable StringLiteral where
ppr sl = pprWithSourceText (sl_st sl) (ftext $ sl_fs sl)
instance Binary StringLiteral where
put_ bh (StringLiteral st fs _) = do
put_ bh st
put_ bh fs
get bh = do
st <- get bh
fs <- get bh
return (StringLiteral st fs Nothing)