{-# LANGUAGE CPP #-}
module GHC.SourceGen.Lit.Internal where
#if MIN_VERSION_ghc(9,2,0)
import GHC.Types.SourceText (SourceText(NoSourceText), FractionalLit(..), IntegralLit(..))
#elif MIN_VERSION_ghc(9,0,0)
import GHC.Types.Basic (SourceText(NoSourceText), FractionalLit(..), IntegralLit(..))
#else
import BasicTypes (SourceText(NoSourceText), FractionalLit(..), IntegralLit(..))
#endif
import GHC.Hs.Lit
import GHC.SourceGen.Syntax.Internal
noSourceText :: (SourceText -> a) -> a
noSourceText :: (SourceText -> a) -> a
noSourceText = ((SourceText -> a) -> SourceText -> a
forall a b. (a -> b) -> a -> b
$ SourceText
NoSourceText)
litNeedsParen :: HsLit' -> Bool
litNeedsParen :: HsLit' -> Bool
litNeedsParen HsLit'
_ = Bool
False
overLitNeedsParen :: HsOverLit' -> Bool
overLitNeedsParen :: HsOverLit' -> Bool
overLitNeedsParen = OverLitVal -> Bool
needs (OverLitVal -> Bool)
-> (HsOverLit' -> OverLitVal) -> HsOverLit' -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HsOverLit' -> OverLitVal
forall p. HsOverLit p -> OverLitVal
ol_val
where
needs :: OverLitVal -> Bool
needs (HsIntegral IntegralLit
x) = IntegralLit -> Bool
il_neg IntegralLit
x
needs (HsFractional FractionalLit
x) = FractionalLit -> Bool
fl_neg FractionalLit
x
needs OverLitVal
_ = Bool
False