{-# LANGUAGE DeriveDataTypeable #-}
module BasicTypes(
Version, bumpVersion, initialVersion,
LeftOrRight(..),
pickLR,
ConTag, ConTagZ, fIRST_TAG,
Arity, RepArity, JoinArity,
Alignment,
PromotionFlag(..), isPromoted,
FunctionOrData(..),
WarningTxt(..), pprWarningTxtForMsg, StringLiteral(..),
Fixity(..), FixityDirection(..),
defaultFixity, maxPrecedence, minPrecedence,
negateFixity, funTyFixity,
compareFixity,
LexicalFixity(..),
RecFlag(..), isRec, isNonRec, boolToRecFlag,
Origin(..), isGenerated,
RuleName, pprRuleName,
TopLevelFlag(..), isTopLevel, isNotTopLevel,
OverlapFlag(..), OverlapMode(..), setOverlapModeMaybe,
hasOverlappingFlag, hasOverlappableFlag, hasIncoherentFlag,
Boxity(..), isBoxed,
PprPrec(..), topPrec, sigPrec, opPrec, funPrec, appPrec, maybeParen,
TupleSort(..), tupleSortBoxity, boxityTupleSort,
tupleParens,
sumParens, pprAlternative,
OneShotInfo(..),
noOneShotInfo, hasNoOneShotInfo, isOneShotInfo,
bestOneShot, worstOneShot,
OccInfo(..), noOccInfo, seqOccInfo, zapFragileOcc, isOneOcc,
isDeadOcc, isStrongLoopBreaker, isWeakLoopBreaker, isManyOccs,
strongLoopBreaker, weakLoopBreaker,
InsideLam, insideLam, notInsideLam,
OneBranch, oneBranch, notOneBranch,
InterestingCxt,
TailCallInfo(..), tailCallInfo, zapOccTailCallInfo,
isAlwaysTailCalled,
EP(..),
DefMethSpec(..),
SwapFlag(..), flipSwap, unSwap, isSwapped,
CompilerPhase(..), PhaseNum,
Activation(..), isActive, isActiveIn, competesWith,
isNeverActive, isAlwaysActive, isEarlyActive,
activeAfterInitial, activeDuringFinal,
RuleMatchInfo(..), isConLike, isFunLike,
InlineSpec(..), noUserInlineSpec,
InlinePragma(..), defaultInlinePragma, alwaysInlinePragma,
neverInlinePragma, dfunInlinePragma,
isDefaultInlinePragma,
isInlinePragma, isInlinablePragma, isAnyInlinePragma,
inlinePragmaSpec, inlinePragmaSat,
inlinePragmaActivation, inlinePragmaRuleMatchInfo,
setInlinePragmaActivation, setInlinePragmaRuleMatchInfo,
pprInline, pprInlineDebug,
SuccessFlag(..), succeeded, failed, successIf,
IntegralLit(..), FractionalLit(..),
negateIntegralLit, negateFractionalLit,
mkIntegralLit, mkFractionalLit,
integralFractionalLit,
SourceText(..), pprWithSourceText,
IntWithInf, infinity, treatZeroAsInf, mkIntWithInf, intGtLimit,
SpliceExplicitFlag(..)
) where
import GhcPrelude
import FastString
import Outputable
import SrcLoc ( Located,unLoc )
import Data.Data hiding (Fixity, Prefix, Infix)
import Data.Function (on)
data LeftOrRight = CLeft | CRight
deriving( LeftOrRight -> LeftOrRight -> Bool
(LeftOrRight -> LeftOrRight -> Bool)
-> (LeftOrRight -> LeftOrRight -> Bool) -> Eq LeftOrRight
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LeftOrRight -> LeftOrRight -> Bool
$c/= :: LeftOrRight -> LeftOrRight -> Bool
== :: LeftOrRight -> LeftOrRight -> Bool
$c== :: LeftOrRight -> LeftOrRight -> Bool
Eq, Typeable LeftOrRight
DataType
Constr
Typeable LeftOrRight
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight)
-> (LeftOrRight -> Constr)
-> (LeftOrRight -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LeftOrRight))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LeftOrRight))
-> ((forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r)
-> (forall u. (forall d. Data d => d -> u) -> LeftOrRight -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight)
-> Data LeftOrRight
LeftOrRight -> DataType
LeftOrRight -> Constr
(forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight
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) -> LeftOrRight -> u
forall u. (forall d. Data d => d -> u) -> LeftOrRight -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LeftOrRight)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LeftOrRight)
$cCRight :: Constr
$cCLeft :: Constr
$tLeftOrRight :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
gmapMp :: (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
gmapM :: (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u
gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LeftOrRight -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight
$cgmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LeftOrRight)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LeftOrRight)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LeftOrRight)
dataTypeOf :: LeftOrRight -> DataType
$cdataTypeOf :: LeftOrRight -> DataType
toConstr :: LeftOrRight -> Constr
$ctoConstr :: LeftOrRight -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight
$cp1Data :: Typeable LeftOrRight
Data )
pickLR :: LeftOrRight -> (a,a) -> a
pickLR :: LeftOrRight -> (a, a) -> a
pickLR LeftOrRight
CLeft (a
l,a
_) = a
l
pickLR LeftOrRight
CRight (a
_,a
r) = a
r
instance Outputable LeftOrRight where
ppr :: LeftOrRight -> SDoc
ppr LeftOrRight
CLeft = String -> SDoc
text String
"Left"
ppr LeftOrRight
CRight = String -> SDoc
text String
"Right"
type Arity = Int
type RepArity = Int
type JoinArity = Int
type ConTag = Int
type ConTagZ = Int
fIRST_TAG :: ConTag
fIRST_TAG :: Int
fIRST_TAG = Int
1
type Alignment = Int
data OneShotInfo
= NoOneShotInfo
| OneShotLam
deriving (OneShotInfo -> OneShotInfo -> Bool
(OneShotInfo -> OneShotInfo -> Bool)
-> (OneShotInfo -> OneShotInfo -> Bool) -> Eq OneShotInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OneShotInfo -> OneShotInfo -> Bool
$c/= :: OneShotInfo -> OneShotInfo -> Bool
== :: OneShotInfo -> OneShotInfo -> Bool
$c== :: OneShotInfo -> OneShotInfo -> Bool
Eq)
noOneShotInfo :: OneShotInfo
noOneShotInfo :: OneShotInfo
noOneShotInfo = OneShotInfo
NoOneShotInfo
isOneShotInfo, hasNoOneShotInfo :: OneShotInfo -> Bool
isOneShotInfo :: OneShotInfo -> Bool
isOneShotInfo OneShotInfo
OneShotLam = Bool
True
isOneShotInfo OneShotInfo
_ = Bool
False
hasNoOneShotInfo :: OneShotInfo -> Bool
hasNoOneShotInfo OneShotInfo
NoOneShotInfo = Bool
True
hasNoOneShotInfo OneShotInfo
_ = Bool
False
worstOneShot, bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
worstOneShot OneShotInfo
NoOneShotInfo OneShotInfo
_ = OneShotInfo
NoOneShotInfo
worstOneShot OneShotInfo
OneShotLam OneShotInfo
os = OneShotInfo
os
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
bestOneShot OneShotInfo
NoOneShotInfo OneShotInfo
os = OneShotInfo
os
bestOneShot OneShotInfo
OneShotLam OneShotInfo
_ = OneShotInfo
OneShotLam
pprOneShotInfo :: OneShotInfo -> SDoc
pprOneShotInfo :: OneShotInfo -> SDoc
pprOneShotInfo OneShotInfo
NoOneShotInfo = SDoc
empty
pprOneShotInfo OneShotInfo
OneShotLam = String -> SDoc
text String
"OneShot"
instance Outputable OneShotInfo where
ppr :: OneShotInfo -> SDoc
ppr = OneShotInfo -> SDoc
pprOneShotInfo
data SwapFlag
= NotSwapped
| IsSwapped
instance Outputable SwapFlag where
ppr :: SwapFlag -> SDoc
ppr SwapFlag
IsSwapped = String -> SDoc
text String
"Is-swapped"
ppr SwapFlag
NotSwapped = String -> SDoc
text String
"Not-swapped"
flipSwap :: SwapFlag -> SwapFlag
flipSwap :: SwapFlag -> SwapFlag
flipSwap SwapFlag
IsSwapped = SwapFlag
NotSwapped
flipSwap SwapFlag
NotSwapped = SwapFlag
IsSwapped
isSwapped :: SwapFlag -> Bool
isSwapped :: SwapFlag -> Bool
isSwapped SwapFlag
IsSwapped = Bool
True
isSwapped SwapFlag
NotSwapped = Bool
False
unSwap :: SwapFlag -> (a->a->b) -> a -> a -> b
unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b
unSwap SwapFlag
NotSwapped a -> a -> b
f a
a a
b = a -> a -> b
f a
a a
b
unSwap SwapFlag
IsSwapped a -> a -> b
f a
a a
b = a -> a -> b
f a
b a
a
data PromotionFlag
= NotPromoted
| IsPromoted
deriving ( PromotionFlag -> PromotionFlag -> Bool
(PromotionFlag -> PromotionFlag -> Bool)
-> (PromotionFlag -> PromotionFlag -> Bool) -> Eq PromotionFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PromotionFlag -> PromotionFlag -> Bool
$c/= :: PromotionFlag -> PromotionFlag -> Bool
== :: PromotionFlag -> PromotionFlag -> Bool
$c== :: PromotionFlag -> PromotionFlag -> Bool
Eq, Typeable PromotionFlag
DataType
Constr
Typeable PromotionFlag
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag)
-> (PromotionFlag -> Constr)
-> (PromotionFlag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag))
-> ((forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r)
-> (forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag)
-> Data PromotionFlag
PromotionFlag -> DataType
PromotionFlag -> Constr
(forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
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) -> PromotionFlag -> u
forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag)
$cIsPromoted :: Constr
$cNotPromoted :: Constr
$tPromotionFlag :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
gmapMp :: (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
gmapM :: (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u
gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag
$cgmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag)
dataTypeOf :: PromotionFlag -> DataType
$cdataTypeOf :: PromotionFlag -> DataType
toConstr :: PromotionFlag -> Constr
$ctoConstr :: PromotionFlag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
$cp1Data :: Typeable PromotionFlag
Data )
isPromoted :: PromotionFlag -> Bool
isPromoted :: PromotionFlag -> Bool
isPromoted PromotionFlag
IsPromoted = Bool
True
isPromoted PromotionFlag
NotPromoted = Bool
False
data FunctionOrData = IsFunction | IsData
deriving (FunctionOrData -> FunctionOrData -> Bool
(FunctionOrData -> FunctionOrData -> Bool)
-> (FunctionOrData -> FunctionOrData -> Bool) -> Eq FunctionOrData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunctionOrData -> FunctionOrData -> Bool
$c/= :: FunctionOrData -> FunctionOrData -> Bool
== :: FunctionOrData -> FunctionOrData -> Bool
$c== :: FunctionOrData -> FunctionOrData -> Bool
Eq, Eq FunctionOrData
Eq FunctionOrData
-> (FunctionOrData -> FunctionOrData -> Ordering)
-> (FunctionOrData -> FunctionOrData -> Bool)
-> (FunctionOrData -> FunctionOrData -> Bool)
-> (FunctionOrData -> FunctionOrData -> Bool)
-> (FunctionOrData -> FunctionOrData -> Bool)
-> (FunctionOrData -> FunctionOrData -> FunctionOrData)
-> (FunctionOrData -> FunctionOrData -> FunctionOrData)
-> Ord FunctionOrData
FunctionOrData -> FunctionOrData -> Bool
FunctionOrData -> FunctionOrData -> Ordering
FunctionOrData -> FunctionOrData -> FunctionOrData
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 :: FunctionOrData -> FunctionOrData -> FunctionOrData
$cmin :: FunctionOrData -> FunctionOrData -> FunctionOrData
max :: FunctionOrData -> FunctionOrData -> FunctionOrData
$cmax :: FunctionOrData -> FunctionOrData -> FunctionOrData
>= :: FunctionOrData -> FunctionOrData -> Bool
$c>= :: FunctionOrData -> FunctionOrData -> Bool
> :: FunctionOrData -> FunctionOrData -> Bool
$c> :: FunctionOrData -> FunctionOrData -> Bool
<= :: FunctionOrData -> FunctionOrData -> Bool
$c<= :: FunctionOrData -> FunctionOrData -> Bool
< :: FunctionOrData -> FunctionOrData -> Bool
$c< :: FunctionOrData -> FunctionOrData -> Bool
compare :: FunctionOrData -> FunctionOrData -> Ordering
$ccompare :: FunctionOrData -> FunctionOrData -> Ordering
$cp1Ord :: Eq FunctionOrData
Ord, Typeable FunctionOrData
DataType
Constr
Typeable FunctionOrData
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData)
-> (FunctionOrData -> Constr)
-> (FunctionOrData -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionOrData))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionOrData))
-> ((forall b. Data b => b -> b)
-> FunctionOrData -> FunctionOrData)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r)
-> (forall u.
(forall d. Data d => d -> u) -> FunctionOrData -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FunctionOrData -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData)
-> Data FunctionOrData
FunctionOrData -> DataType
FunctionOrData -> Constr
(forall b. Data b => b -> b) -> FunctionOrData -> FunctionOrData
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData
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) -> FunctionOrData -> u
forall u. (forall d. Data d => d -> u) -> FunctionOrData -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionOrData)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionOrData)
$cIsData :: Constr
$cIsFunction :: Constr
$tFunctionOrData :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
gmapMp :: (forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
gmapM :: (forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionOrData -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FunctionOrData -> u
gmapQ :: (forall d. Data d => d -> u) -> FunctionOrData -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FunctionOrData -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
gmapT :: (forall b. Data b => b -> b) -> FunctionOrData -> FunctionOrData
$cgmapT :: (forall b. Data b => b -> b) -> FunctionOrData -> FunctionOrData
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionOrData)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionOrData)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FunctionOrData)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionOrData)
dataTypeOf :: FunctionOrData -> DataType
$cdataTypeOf :: FunctionOrData -> DataType
toConstr :: FunctionOrData -> Constr
$ctoConstr :: FunctionOrData -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData
$cp1Data :: Typeable FunctionOrData
Data)
instance Outputable FunctionOrData where
ppr :: FunctionOrData -> SDoc
ppr FunctionOrData
IsFunction = String -> SDoc
text String
"(function)"
ppr FunctionOrData
IsData = String -> SDoc
text String
"(data)"
type Version = Int
bumpVersion :: Version -> Version
bumpVersion :: Int -> Int
bumpVersion Int
v = Int
vInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1
initialVersion :: Version
initialVersion :: Int
initialVersion = Int
1
data StringLiteral = StringLiteral
{ StringLiteral -> SourceText
sl_st :: SourceText,
StringLiteral -> FastString
sl_fs :: FastString
} 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) == :: StringLiteral -> StringLiteral -> Bool
== (StringLiteral SourceText
_ FastString
b) = 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)
data WarningTxt = WarningTxt (Located SourceText)
[Located StringLiteral]
| DeprecatedTxt (Located SourceText)
[Located StringLiteral]
deriving (WarningTxt -> WarningTxt -> Bool
(WarningTxt -> WarningTxt -> Bool)
-> (WarningTxt -> WarningTxt -> Bool) -> Eq WarningTxt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WarningTxt -> WarningTxt -> Bool
$c/= :: WarningTxt -> WarningTxt -> Bool
== :: WarningTxt -> WarningTxt -> Bool
$c== :: WarningTxt -> WarningTxt -> Bool
Eq, Typeable WarningTxt
DataType
Constr
Typeable WarningTxt
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarningTxt -> c WarningTxt)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarningTxt)
-> (WarningTxt -> Constr)
-> (WarningTxt -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WarningTxt))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WarningTxt))
-> ((forall b. Data b => b -> b) -> WarningTxt -> WarningTxt)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r)
-> (forall u. (forall d. Data d => d -> u) -> WarningTxt -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> WarningTxt -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt)
-> Data WarningTxt
WarningTxt -> DataType
WarningTxt -> Constr
(forall b. Data b => b -> b) -> WarningTxt -> WarningTxt
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarningTxt -> c WarningTxt
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarningTxt
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) -> WarningTxt -> u
forall u. (forall d. Data d => d -> u) -> WarningTxt -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarningTxt
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarningTxt -> c WarningTxt
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WarningTxt)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningTxt)
$cDeprecatedTxt :: Constr
$cWarningTxt :: Constr
$tWarningTxt :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
gmapMp :: (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
gmapM :: (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt
gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningTxt -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WarningTxt -> u
gmapQ :: (forall d. Data d => d -> u) -> WarningTxt -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WarningTxt -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WarningTxt -> r
gmapT :: (forall b. Data b => b -> b) -> WarningTxt -> WarningTxt
$cgmapT :: (forall b. Data b => b -> b) -> WarningTxt -> WarningTxt
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningTxt)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningTxt)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c WarningTxt)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WarningTxt)
dataTypeOf :: WarningTxt -> DataType
$cdataTypeOf :: WarningTxt -> DataType
toConstr :: WarningTxt -> Constr
$ctoConstr :: WarningTxt -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarningTxt
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WarningTxt
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarningTxt -> c WarningTxt
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WarningTxt -> c WarningTxt
$cp1Data :: Typeable WarningTxt
Data)
instance Outputable WarningTxt where
ppr :: WarningTxt -> SDoc
ppr (WarningTxt Located SourceText
lsrc [Located StringLiteral]
ws)
= case Located SourceText -> SrcSpanLess (Located SourceText)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located SourceText
lsrc of
SrcSpanLess (Located SourceText)
NoSourceText -> [Located StringLiteral] -> SDoc
pp_ws [Located StringLiteral]
ws
SourceText src -> String -> SDoc
text String
src SDoc -> SDoc -> SDoc
<+> [Located StringLiteral] -> SDoc
pp_ws [Located StringLiteral]
ws SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"#-}"
ppr (DeprecatedTxt Located SourceText
lsrc [Located StringLiteral]
ds)
= case Located SourceText -> SrcSpanLess (Located SourceText)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located SourceText
lsrc of
SrcSpanLess (Located SourceText)
NoSourceText -> [Located StringLiteral] -> SDoc
pp_ws [Located StringLiteral]
ds
SourceText src -> String -> SDoc
text String
src SDoc -> SDoc -> SDoc
<+> [Located StringLiteral] -> SDoc
pp_ws [Located StringLiteral]
ds SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"#-}"
pp_ws :: [Located StringLiteral] -> SDoc
pp_ws :: [Located StringLiteral] -> SDoc
pp_ws [Located StringLiteral
l] = StringLiteral -> SDoc
forall a. Outputable a => a -> SDoc
ppr (StringLiteral -> SDoc) -> StringLiteral -> SDoc
forall a b. (a -> b) -> a -> b
$ Located StringLiteral -> SrcSpanLess (Located StringLiteral)
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc Located StringLiteral
l
pp_ws [Located StringLiteral]
ws
= String -> SDoc
text String
"["
SDoc -> SDoc -> SDoc
<+> [SDoc] -> SDoc
vcat (SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ((Located StringLiteral -> SDoc)
-> [Located StringLiteral] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (StringLiteral -> SDoc
forall a. Outputable a => a -> SDoc
ppr (StringLiteral -> SDoc)
-> (Located StringLiteral -> StringLiteral)
-> Located StringLiteral
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located StringLiteral -> StringLiteral
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [Located StringLiteral]
ws))
SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"]"
pprWarningTxtForMsg :: WarningTxt -> SDoc
pprWarningTxtForMsg :: WarningTxt -> SDoc
pprWarningTxtForMsg (WarningTxt Located SourceText
_ [Located StringLiteral]
ws)
= SDoc -> SDoc
doubleQuotes ([SDoc] -> SDoc
vcat ((Located StringLiteral -> SDoc)
-> [Located StringLiteral] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (FastString -> SDoc
ftext (FastString -> SDoc)
-> (Located StringLiteral -> FastString)
-> Located StringLiteral
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringLiteral -> FastString
sl_fs (StringLiteral -> FastString)
-> (Located StringLiteral -> StringLiteral)
-> Located StringLiteral
-> FastString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located StringLiteral -> StringLiteral
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [Located StringLiteral]
ws))
pprWarningTxtForMsg (DeprecatedTxt Located SourceText
_ [Located StringLiteral]
ds)
= String -> SDoc
text String
"Deprecated:" SDoc -> SDoc -> SDoc
<+>
SDoc -> SDoc
doubleQuotes ([SDoc] -> SDoc
vcat ((Located StringLiteral -> SDoc)
-> [Located StringLiteral] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map (FastString -> SDoc
ftext (FastString -> SDoc)
-> (Located StringLiteral -> FastString)
-> Located StringLiteral
-> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringLiteral -> FastString
sl_fs (StringLiteral -> FastString)
-> (Located StringLiteral -> StringLiteral)
-> Located StringLiteral
-> FastString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Located StringLiteral -> StringLiteral
forall a. HasSrcSpan a => a -> SrcSpanLess a
unLoc) [Located StringLiteral]
ds))
type RuleName = FastString
pprRuleName :: RuleName -> SDoc
pprRuleName :: FastString -> SDoc
pprRuleName FastString
rn = SDoc -> SDoc
doubleQuotes (FastString -> SDoc
ftext FastString
rn)
data Fixity = Fixity SourceText Int FixityDirection
deriving Typeable Fixity
DataType
Constr
Typeable Fixity
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Fixity -> c Fixity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Fixity)
-> (Fixity -> Constr)
-> (Fixity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Fixity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity))
-> ((forall b. Data b => b -> b) -> Fixity -> Fixity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Fixity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Fixity -> r)
-> (forall u. (forall d. Data d => d -> u) -> Fixity -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Fixity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity)
-> Data Fixity
Fixity -> DataType
Fixity -> Constr
(forall b. Data b => b -> b) -> Fixity -> Fixity
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Fixity -> c Fixity
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Fixity
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) -> Fixity -> u
forall u. (forall d. Data d => d -> u) -> Fixity -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Fixity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Fixity -> c Fixity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Fixity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity)
$cFixity :: Constr
$tFixity :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Fixity -> m Fixity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity
gmapMp :: (forall d. Data d => d -> m d) -> Fixity -> m Fixity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity
gmapM :: (forall d. Data d => d -> m d) -> Fixity -> m Fixity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Fixity -> m Fixity
gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Fixity -> u
gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Fixity -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r
gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity
$cgmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Fixity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Fixity)
dataTypeOf :: Fixity -> DataType
$cdataTypeOf :: Fixity -> DataType
toConstr :: Fixity -> Constr
$ctoConstr :: Fixity -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Fixity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Fixity
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Fixity -> c Fixity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Fixity -> c Fixity
$cp1Data :: Typeable Fixity
Data
instance Outputable Fixity where
ppr :: Fixity -> SDoc
ppr (Fixity SourceText
_ Int
prec FixityDirection
dir) = [SDoc] -> SDoc
hcat [FixityDirection -> SDoc
forall a. Outputable a => a -> SDoc
ppr FixityDirection
dir, SDoc
space, Int -> SDoc
int Int
prec]
instance Eq Fixity where
(Fixity SourceText
_ Int
p1 FixityDirection
dir1) == :: Fixity -> Fixity -> Bool
== (Fixity SourceText
_ Int
p2 FixityDirection
dir2) = Int
p1Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
p2 Bool -> Bool -> Bool
&& FixityDirection
dir1 FixityDirection -> FixityDirection -> Bool
forall a. Eq a => a -> a -> Bool
== FixityDirection
dir2
data FixityDirection = InfixL | InfixR | InfixN
deriving (FixityDirection -> FixityDirection -> Bool
(FixityDirection -> FixityDirection -> Bool)
-> (FixityDirection -> FixityDirection -> Bool)
-> Eq FixityDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FixityDirection -> FixityDirection -> Bool
$c/= :: FixityDirection -> FixityDirection -> Bool
== :: FixityDirection -> FixityDirection -> Bool
$c== :: FixityDirection -> FixityDirection -> Bool
Eq, Typeable FixityDirection
DataType
Constr
Typeable FixityDirection
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixityDirection -> c FixityDirection)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixityDirection)
-> (FixityDirection -> Constr)
-> (FixityDirection -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FixityDirection))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixityDirection))
-> ((forall b. Data b => b -> b)
-> FixityDirection -> FixityDirection)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r)
-> (forall u.
(forall d. Data d => d -> u) -> FixityDirection -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> FixityDirection -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection)
-> Data FixityDirection
FixityDirection -> DataType
FixityDirection -> Constr
(forall b. Data b => b -> b) -> FixityDirection -> FixityDirection
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixityDirection -> c FixityDirection
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixityDirection
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) -> FixityDirection -> u
forall u. (forall d. Data d => d -> u) -> FixityDirection -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixityDirection
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixityDirection -> c FixityDirection
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FixityDirection)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixityDirection)
$cInfixN :: Constr
$cInfixR :: Constr
$cInfixL :: Constr
$tFixityDirection :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
gmapMp :: (forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
gmapM :: (forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FixityDirection -> m FixityDirection
gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FixityDirection -> u
gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FixityDirection -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FixityDirection -> r
gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection
$cgmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixityDirection)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FixityDirection)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FixityDirection)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FixityDirection)
dataTypeOf :: FixityDirection -> DataType
$cdataTypeOf :: FixityDirection -> DataType
toConstr :: FixityDirection -> Constr
$ctoConstr :: FixityDirection -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixityDirection
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FixityDirection
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixityDirection -> c FixityDirection
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FixityDirection -> c FixityDirection
$cp1Data :: Typeable FixityDirection
Data)
instance Outputable FixityDirection where
ppr :: FixityDirection -> SDoc
ppr FixityDirection
InfixL = String -> SDoc
text String
"infixl"
ppr FixityDirection
InfixR = String -> SDoc
text String
"infixr"
ppr FixityDirection
InfixN = String -> SDoc
text String
"infix"
maxPrecedence, minPrecedence :: Int
maxPrecedence :: Int
maxPrecedence = Int
9
minPrecedence :: Int
minPrecedence = Int
0
defaultFixity :: Fixity
defaultFixity :: Fixity
defaultFixity = SourceText -> Int -> FixityDirection -> Fixity
Fixity SourceText
NoSourceText Int
maxPrecedence FixityDirection
InfixL
negateFixity, funTyFixity :: Fixity
negateFixity :: Fixity
negateFixity = SourceText -> Int -> FixityDirection -> Fixity
Fixity SourceText
NoSourceText Int
6 FixityDirection
InfixL
funTyFixity :: Fixity
funTyFixity = SourceText -> Int -> FixityDirection -> Fixity
Fixity SourceText
NoSourceText (-Int
1) FixityDirection
InfixR
compareFixity :: Fixity -> Fixity
-> (Bool,
Bool)
compareFixity :: Fixity -> Fixity -> (Bool, Bool)
compareFixity (Fixity SourceText
_ Int
prec1 FixityDirection
dir1) (Fixity SourceText
_ Int
prec2 FixityDirection
dir2)
= case Int
prec1 Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Int
prec2 of
Ordering
GT -> (Bool, Bool)
left
Ordering
LT -> (Bool, Bool)
right
Ordering
EQ -> case (FixityDirection
dir1, FixityDirection
dir2) of
(FixityDirection
InfixR, FixityDirection
InfixR) -> (Bool, Bool)
right
(FixityDirection
InfixL, FixityDirection
InfixL) -> (Bool, Bool)
left
(FixityDirection, FixityDirection)
_ -> (Bool, Bool)
error_please
where
right :: (Bool, Bool)
right = (Bool
False, Bool
True)
left :: (Bool, Bool)
left = (Bool
False, Bool
False)
error_please :: (Bool, Bool)
error_please = (Bool
True, Bool
False)
data LexicalFixity = Prefix | Infix deriving (Typeable LexicalFixity
DataType
Constr
Typeable LexicalFixity
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFixity)
-> (LexicalFixity -> Constr)
-> (LexicalFixity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFixity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFixity))
-> ((forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r)
-> (forall u. (forall d. Data d => d -> u) -> LexicalFixity -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity)
-> Data LexicalFixity
LexicalFixity -> DataType
LexicalFixity -> Constr
(forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFixity
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) -> LexicalFixity -> u
forall u. (forall d. Data d => d -> u) -> LexicalFixity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFixity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFixity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFixity)
$cInfix :: Constr
$cPrefix :: Constr
$tLexicalFixity :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
gmapMp :: (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
gmapM :: (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity
gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u
gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LexicalFixity -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r
gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity
$cgmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFixity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LexicalFixity)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LexicalFixity)
dataTypeOf :: LexicalFixity -> DataType
$cdataTypeOf :: LexicalFixity -> DataType
toConstr :: LexicalFixity -> Constr
$ctoConstr :: LexicalFixity -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFixity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LexicalFixity
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity
$cp1Data :: Typeable LexicalFixity
Data,LexicalFixity -> LexicalFixity -> Bool
(LexicalFixity -> LexicalFixity -> Bool)
-> (LexicalFixity -> LexicalFixity -> Bool) -> Eq LexicalFixity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LexicalFixity -> LexicalFixity -> Bool
$c/= :: LexicalFixity -> LexicalFixity -> Bool
== :: LexicalFixity -> LexicalFixity -> Bool
$c== :: LexicalFixity -> LexicalFixity -> Bool
Eq)
instance Outputable LexicalFixity where
ppr :: LexicalFixity -> SDoc
ppr LexicalFixity
Prefix = String -> SDoc
text String
"Prefix"
ppr LexicalFixity
Infix = String -> SDoc
text String
"Infix"
data TopLevelFlag
= TopLevel
| NotTopLevel
isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool
isNotTopLevel :: TopLevelFlag -> Bool
isNotTopLevel TopLevelFlag
NotTopLevel = Bool
True
isNotTopLevel TopLevelFlag
TopLevel = Bool
False
isTopLevel :: TopLevelFlag -> Bool
isTopLevel TopLevelFlag
TopLevel = Bool
True
isTopLevel TopLevelFlag
NotTopLevel = Bool
False
instance Outputable TopLevelFlag where
ppr :: TopLevelFlag -> SDoc
ppr TopLevelFlag
TopLevel = String -> SDoc
text String
"<TopLevel>"
ppr TopLevelFlag
NotTopLevel = String -> SDoc
text String
"<NotTopLevel>"
data Boxity
= Boxed
| Unboxed
deriving( Boxity -> Boxity -> Bool
(Boxity -> Boxity -> Bool)
-> (Boxity -> Boxity -> Bool) -> Eq Boxity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Boxity -> Boxity -> Bool
$c/= :: Boxity -> Boxity -> Bool
== :: Boxity -> Boxity -> Bool
$c== :: Boxity -> Boxity -> Bool
Eq, Typeable Boxity
DataType
Constr
Typeable Boxity
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Boxity -> c Boxity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Boxity)
-> (Boxity -> Constr)
-> (Boxity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Boxity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity))
-> ((forall b. Data b => b -> b) -> Boxity -> Boxity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Boxity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Boxity -> r)
-> (forall u. (forall d. Data d => d -> u) -> Boxity -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Boxity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity)
-> Data Boxity
Boxity -> DataType
Boxity -> Constr
(forall b. Data b => b -> b) -> Boxity -> Boxity
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Boxity -> c Boxity
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Boxity
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) -> Boxity -> u
forall u. (forall d. Data d => d -> u) -> Boxity -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Boxity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Boxity -> c Boxity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Boxity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity)
$cUnboxed :: Constr
$cBoxed :: Constr
$tBoxity :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Boxity -> m Boxity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity
gmapMp :: (forall d. Data d => d -> m d) -> Boxity -> m Boxity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity
gmapM :: (forall d. Data d => d -> m d) -> Boxity -> m Boxity
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Boxity -> m Boxity
gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxity -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Boxity -> u
gmapQ :: (forall d. Data d => d -> u) -> Boxity -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Boxity -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r
gmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity
$cgmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Boxity)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Boxity)
dataTypeOf :: Boxity -> DataType
$cdataTypeOf :: Boxity -> DataType
toConstr :: Boxity -> Constr
$ctoConstr :: Boxity -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Boxity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Boxity
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Boxity -> c Boxity
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Boxity -> c Boxity
$cp1Data :: Typeable Boxity
Data )
isBoxed :: Boxity -> Bool
isBoxed :: Boxity -> Bool
isBoxed Boxity
Boxed = Bool
True
isBoxed Boxity
Unboxed = Bool
False
instance Outputable Boxity where
ppr :: Boxity -> SDoc
ppr Boxity
Boxed = String -> SDoc
text String
"Boxed"
ppr Boxity
Unboxed = String -> SDoc
text String
"Unboxed"
data RecFlag = Recursive
| NonRecursive
deriving( RecFlag -> RecFlag -> Bool
(RecFlag -> RecFlag -> Bool)
-> (RecFlag -> RecFlag -> Bool) -> Eq RecFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecFlag -> RecFlag -> Bool
$c/= :: RecFlag -> RecFlag -> Bool
== :: RecFlag -> RecFlag -> Bool
$c== :: RecFlag -> RecFlag -> Bool
Eq, Typeable RecFlag
DataType
Constr
Typeable RecFlag
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag)
-> (RecFlag -> Constr)
-> (RecFlag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecFlag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag))
-> ((forall b. Data b => b -> b) -> RecFlag -> RecFlag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r)
-> (forall u. (forall d. Data d => d -> u) -> RecFlag -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> RecFlag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag)
-> Data RecFlag
RecFlag -> DataType
RecFlag -> Constr
(forall b. Data b => b -> b) -> RecFlag -> RecFlag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag
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) -> RecFlag -> u
forall u. (forall d. Data d => d -> u) -> RecFlag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecFlag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag)
$cNonRecursive :: Constr
$cRecursive :: Constr
$tRecFlag :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
gmapMp :: (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
gmapM :: (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFlag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RecFlag -> u
gmapQ :: (forall d. Data d => d -> u) -> RecFlag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RecFlag -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag
$cgmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RecFlag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecFlag)
dataTypeOf :: RecFlag -> DataType
$cdataTypeOf :: RecFlag -> DataType
toConstr :: RecFlag -> Constr
$ctoConstr :: RecFlag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag
$cp1Data :: Typeable RecFlag
Data )
isRec :: RecFlag -> Bool
isRec :: RecFlag -> Bool
isRec RecFlag
Recursive = Bool
True
isRec RecFlag
NonRecursive = Bool
False
isNonRec :: RecFlag -> Bool
isNonRec :: RecFlag -> Bool
isNonRec RecFlag
Recursive = Bool
False
isNonRec RecFlag
NonRecursive = Bool
True
boolToRecFlag :: Bool -> RecFlag
boolToRecFlag :: Bool -> RecFlag
boolToRecFlag Bool
True = RecFlag
Recursive
boolToRecFlag Bool
False = RecFlag
NonRecursive
instance Outputable RecFlag where
ppr :: RecFlag -> SDoc
ppr RecFlag
Recursive = String -> SDoc
text String
"Recursive"
ppr RecFlag
NonRecursive = String -> SDoc
text String
"NonRecursive"
data Origin = FromSource
| Generated
deriving( Origin -> Origin -> Bool
(Origin -> Origin -> Bool)
-> (Origin -> Origin -> Bool) -> Eq Origin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Origin -> Origin -> Bool
$c/= :: Origin -> Origin -> Bool
== :: Origin -> Origin -> Bool
$c== :: Origin -> Origin -> Bool
Eq, Typeable Origin
DataType
Constr
Typeable Origin
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin)
-> (Origin -> Constr)
-> (Origin -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Origin))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin))
-> ((forall b. Data b => b -> b) -> Origin -> Origin)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Origin -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Origin -> r)
-> (forall u. (forall d. Data d => d -> u) -> Origin -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Origin -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin)
-> Data Origin
Origin -> DataType
Origin -> Constr
(forall b. Data b => b -> b) -> Origin -> Origin
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin
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) -> Origin -> u
forall u. (forall d. Data d => d -> u) -> Origin -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Origin)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin)
$cGenerated :: Constr
$cFromSource :: Constr
$tOrigin :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Origin -> m Origin
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin
gmapMp :: (forall d. Data d => d -> m d) -> Origin -> m Origin
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin
gmapM :: (forall d. Data d => d -> m d) -> Origin -> m Origin
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin
gmapQi :: Int -> (forall d. Data d => d -> u) -> Origin -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Origin -> u
gmapQ :: (forall d. Data d => d -> u) -> Origin -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Origin -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin
$cgmapT :: (forall b. Data b => b -> b) -> Origin -> Origin
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Origin)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Origin)
dataTypeOf :: Origin -> DataType
$cdataTypeOf :: Origin -> DataType
toConstr :: Origin -> Constr
$ctoConstr :: Origin -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin
$cp1Data :: Typeable Origin
Data )
isGenerated :: Origin -> Bool
isGenerated :: Origin -> Bool
isGenerated Origin
Generated = Bool
True
isGenerated Origin
FromSource = Bool
False
instance Outputable Origin where
ppr :: Origin -> SDoc
ppr Origin
FromSource = String -> SDoc
text String
"FromSource"
ppr Origin
Generated = String -> SDoc
text String
"Generated"
data OverlapFlag = OverlapFlag
{ OverlapFlag -> OverlapMode
overlapMode :: OverlapMode
, OverlapFlag -> Bool
isSafeOverlap :: Bool
} deriving (OverlapFlag -> OverlapFlag -> Bool
(OverlapFlag -> OverlapFlag -> Bool)
-> (OverlapFlag -> OverlapFlag -> Bool) -> Eq OverlapFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverlapFlag -> OverlapFlag -> Bool
$c/= :: OverlapFlag -> OverlapFlag -> Bool
== :: OverlapFlag -> OverlapFlag -> Bool
$c== :: OverlapFlag -> OverlapFlag -> Bool
Eq, Typeable OverlapFlag
DataType
Constr
Typeable OverlapFlag
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag)
-> (OverlapFlag -> Constr)
-> (OverlapFlag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapFlag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapFlag))
-> ((forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r)
-> (forall u. (forall d. Data d => d -> u) -> OverlapFlag -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag)
-> Data OverlapFlag
OverlapFlag -> DataType
OverlapFlag -> Constr
(forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag
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) -> OverlapFlag -> u
forall u. (forall d. Data d => d -> u) -> OverlapFlag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapFlag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapFlag)
$cOverlapFlag :: Constr
$tOverlapFlag :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
gmapMp :: (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
gmapM :: (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u
gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OverlapFlag -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag
$cgmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapFlag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapFlag)
dataTypeOf :: OverlapFlag -> DataType
$cdataTypeOf :: OverlapFlag -> DataType
toConstr :: OverlapFlag -> Constr
$ctoConstr :: OverlapFlag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag
$cp1Data :: Typeable OverlapFlag
Data)
setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
setOverlapModeMaybe OverlapFlag
f Maybe OverlapMode
Nothing = OverlapFlag
f
setOverlapModeMaybe OverlapFlag
f (Just OverlapMode
m) = OverlapFlag
f { overlapMode :: OverlapMode
overlapMode = OverlapMode
m }
hasIncoherentFlag :: OverlapMode -> Bool
hasIncoherentFlag :: OverlapMode -> Bool
hasIncoherentFlag OverlapMode
mode =
case OverlapMode
mode of
Incoherent SourceText
_ -> Bool
True
OverlapMode
_ -> Bool
False
hasOverlappableFlag :: OverlapMode -> Bool
hasOverlappableFlag :: OverlapMode -> Bool
hasOverlappableFlag OverlapMode
mode =
case OverlapMode
mode of
Overlappable SourceText
_ -> Bool
True
Overlaps SourceText
_ -> Bool
True
Incoherent SourceText
_ -> Bool
True
OverlapMode
_ -> Bool
False
hasOverlappingFlag :: OverlapMode -> Bool
hasOverlappingFlag :: OverlapMode -> Bool
hasOverlappingFlag OverlapMode
mode =
case OverlapMode
mode of
Overlapping SourceText
_ -> Bool
True
Overlaps SourceText
_ -> Bool
True
Incoherent SourceText
_ -> Bool
True
OverlapMode
_ -> Bool
False
data OverlapMode
= NoOverlap SourceText
| Overlappable SourceText
| Overlapping SourceText
| Overlaps SourceText
| Incoherent SourceText
deriving (OverlapMode -> OverlapMode -> Bool
(OverlapMode -> OverlapMode -> Bool)
-> (OverlapMode -> OverlapMode -> Bool) -> Eq OverlapMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverlapMode -> OverlapMode -> Bool
$c/= :: OverlapMode -> OverlapMode -> Bool
== :: OverlapMode -> OverlapMode -> Bool
$c== :: OverlapMode -> OverlapMode -> Bool
Eq, Typeable OverlapMode
DataType
Constr
Typeable OverlapMode
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode)
-> (OverlapMode -> Constr)
-> (OverlapMode -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapMode))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapMode))
-> ((forall b. Data b => b -> b) -> OverlapMode -> OverlapMode)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r)
-> (forall u. (forall d. Data d => d -> u) -> OverlapMode -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OverlapMode -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode)
-> Data OverlapMode
OverlapMode -> DataType
OverlapMode -> Constr
(forall b. Data b => b -> b) -> OverlapMode -> OverlapMode
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode
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) -> OverlapMode -> u
forall u. (forall d. Data d => d -> u) -> OverlapMode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapMode)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapMode)
$cIncoherent :: Constr
$cOverlaps :: Constr
$cOverlapping :: Constr
$cOverlappable :: Constr
$cNoOverlap :: Constr
$tOverlapMode :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
gmapMp :: (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
gmapM :: (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OverlapMode -> u
gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OverlapMode -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode
$cgmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapMode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapMode)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c OverlapMode)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapMode)
dataTypeOf :: OverlapMode -> DataType
$cdataTypeOf :: OverlapMode -> DataType
toConstr :: OverlapMode -> Constr
$ctoConstr :: OverlapMode -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode
$cp1Data :: Typeable OverlapMode
Data)
instance Outputable OverlapFlag where
ppr :: OverlapFlag -> SDoc
ppr OverlapFlag
flag = OverlapMode -> SDoc
forall a. Outputable a => a -> SDoc
ppr (OverlapFlag -> OverlapMode
overlapMode OverlapFlag
flag) SDoc -> SDoc -> SDoc
<+> Bool -> SDoc
pprSafeOverlap (OverlapFlag -> Bool
isSafeOverlap OverlapFlag
flag)
instance Outputable OverlapMode where
ppr :: OverlapMode -> SDoc
ppr (NoOverlap SourceText
_) = SDoc
empty
ppr (Overlappable SourceText
_) = String -> SDoc
text String
"[overlappable]"
ppr (Overlapping SourceText
_) = String -> SDoc
text String
"[overlapping]"
ppr (Overlaps SourceText
_) = String -> SDoc
text String
"[overlap ok]"
ppr (Incoherent SourceText
_) = String -> SDoc
text String
"[incoherent]"
pprSafeOverlap :: Bool -> SDoc
pprSafeOverlap :: Bool -> SDoc
pprSafeOverlap Bool
True = String -> SDoc
text String
"[safe]"
pprSafeOverlap Bool
False = SDoc
empty
newtype PprPrec = PprPrec Int deriving (PprPrec -> PprPrec -> Bool
(PprPrec -> PprPrec -> Bool)
-> (PprPrec -> PprPrec -> Bool) -> Eq PprPrec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PprPrec -> PprPrec -> Bool
$c/= :: PprPrec -> PprPrec -> Bool
== :: PprPrec -> PprPrec -> Bool
$c== :: PprPrec -> PprPrec -> Bool
Eq, Eq PprPrec
Eq PprPrec
-> (PprPrec -> PprPrec -> Ordering)
-> (PprPrec -> PprPrec -> Bool)
-> (PprPrec -> PprPrec -> Bool)
-> (PprPrec -> PprPrec -> Bool)
-> (PprPrec -> PprPrec -> Bool)
-> (PprPrec -> PprPrec -> PprPrec)
-> (PprPrec -> PprPrec -> PprPrec)
-> Ord PprPrec
PprPrec -> PprPrec -> Bool
PprPrec -> PprPrec -> Ordering
PprPrec -> PprPrec -> PprPrec
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 :: PprPrec -> PprPrec -> PprPrec
$cmin :: PprPrec -> PprPrec -> PprPrec
max :: PprPrec -> PprPrec -> PprPrec
$cmax :: PprPrec -> PprPrec -> PprPrec
>= :: PprPrec -> PprPrec -> Bool
$c>= :: PprPrec -> PprPrec -> Bool
> :: PprPrec -> PprPrec -> Bool
$c> :: PprPrec -> PprPrec -> Bool
<= :: PprPrec -> PprPrec -> Bool
$c<= :: PprPrec -> PprPrec -> Bool
< :: PprPrec -> PprPrec -> Bool
$c< :: PprPrec -> PprPrec -> Bool
compare :: PprPrec -> PprPrec -> Ordering
$ccompare :: PprPrec -> PprPrec -> Ordering
$cp1Ord :: Eq PprPrec
Ord, Int -> PprPrec -> ShowS
[PprPrec] -> ShowS
PprPrec -> String
(Int -> PprPrec -> ShowS)
-> (PprPrec -> String) -> ([PprPrec] -> ShowS) -> Show PprPrec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PprPrec] -> ShowS
$cshowList :: [PprPrec] -> ShowS
show :: PprPrec -> String
$cshow :: PprPrec -> String
showsPrec :: Int -> PprPrec -> ShowS
$cshowsPrec :: Int -> PprPrec -> ShowS
Show)
topPrec, sigPrec, funPrec, opPrec, appPrec :: PprPrec
topPrec :: PprPrec
topPrec = Int -> PprPrec
PprPrec Int
0
sigPrec :: PprPrec
sigPrec = Int -> PprPrec
PprPrec Int
1
funPrec :: PprPrec
funPrec = Int -> PprPrec
PprPrec Int
2
opPrec :: PprPrec
opPrec = Int -> PprPrec
PprPrec Int
2
appPrec :: PprPrec
appPrec = Int -> PprPrec
PprPrec Int
3
maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
maybeParen PprPrec
ctxt_prec PprPrec
inner_prec SDoc
pretty
| PprPrec
ctxt_prec PprPrec -> PprPrec -> Bool
forall a. Ord a => a -> a -> Bool
< PprPrec
inner_prec = SDoc
pretty
| Bool
otherwise = SDoc -> SDoc
parens SDoc
pretty
data TupleSort
= BoxedTuple
| UnboxedTuple
| ConstraintTuple
deriving( TupleSort -> TupleSort -> Bool
(TupleSort -> TupleSort -> Bool)
-> (TupleSort -> TupleSort -> Bool) -> Eq TupleSort
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TupleSort -> TupleSort -> Bool
$c/= :: TupleSort -> TupleSort -> Bool
== :: TupleSort -> TupleSort -> Bool
$c== :: TupleSort -> TupleSort -> Bool
Eq, Typeable TupleSort
DataType
Constr
Typeable TupleSort
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort)
-> (TupleSort -> Constr)
-> (TupleSort -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TupleSort))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort))
-> ((forall b. Data b => b -> b) -> TupleSort -> TupleSort)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r)
-> (forall u. (forall d. Data d => d -> u) -> TupleSort -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TupleSort -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort)
-> Data TupleSort
TupleSort -> DataType
TupleSort -> Constr
(forall b. Data b => b -> b) -> TupleSort -> TupleSort
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort
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) -> TupleSort -> u
forall u. (forall d. Data d => d -> u) -> TupleSort -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TupleSort)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort)
$cConstraintTuple :: Constr
$cUnboxedTuple :: Constr
$cBoxedTuple :: Constr
$tTupleSort :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
gmapMp :: (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
gmapM :: (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TupleSort -> u
gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TupleSort -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort
$cgmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TupleSort)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TupleSort)
dataTypeOf :: TupleSort -> DataType
$cdataTypeOf :: TupleSort -> DataType
toConstr :: TupleSort -> Constr
$ctoConstr :: TupleSort -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort
$cp1Data :: Typeable TupleSort
Data )
tupleSortBoxity :: TupleSort -> Boxity
tupleSortBoxity :: TupleSort -> Boxity
tupleSortBoxity TupleSort
BoxedTuple = Boxity
Boxed
tupleSortBoxity TupleSort
UnboxedTuple = Boxity
Unboxed
tupleSortBoxity TupleSort
ConstraintTuple = Boxity
Boxed
boxityTupleSort :: Boxity -> TupleSort
boxityTupleSort :: Boxity -> TupleSort
boxityTupleSort Boxity
Boxed = TupleSort
BoxedTuple
boxityTupleSort Boxity
Unboxed = TupleSort
UnboxedTuple
tupleParens :: TupleSort -> SDoc -> SDoc
tupleParens :: TupleSort -> SDoc -> SDoc
tupleParens TupleSort
BoxedTuple SDoc
p = SDoc -> SDoc
parens SDoc
p
tupleParens TupleSort
UnboxedTuple SDoc
p = String -> SDoc
text String
"(#" SDoc -> SDoc -> SDoc
<+> SDoc
p SDoc -> SDoc -> SDoc
<+> PtrString -> SDoc
ptext (String -> PtrString
sLit String
"#)")
tupleParens TupleSort
ConstraintTuple SDoc
p
= SDoc -> SDoc -> SDoc
ifPprDebug (String -> SDoc
text String
"(%" SDoc -> SDoc -> SDoc
<+> SDoc
p SDoc -> SDoc -> SDoc
<+> PtrString -> SDoc
ptext (String -> PtrString
sLit String
"%)"))
(SDoc -> SDoc
parens SDoc
p)
sumParens :: SDoc -> SDoc
sumParens :: SDoc -> SDoc
sumParens SDoc
p = PtrString -> SDoc
ptext (String -> PtrString
sLit String
"(#") SDoc -> SDoc -> SDoc
<+> SDoc
p SDoc -> SDoc -> SDoc
<+> PtrString -> SDoc
ptext (String -> PtrString
sLit String
"#)")
pprAlternative :: (a -> SDoc)
-> a
-> ConTag
-> Arity
-> SDoc
pprAlternative :: (a -> SDoc) -> a -> Int -> Int -> SDoc
pprAlternative a -> SDoc
pp a
x Int
alt Int
arity =
[SDoc] -> SDoc
fsep (Int -> SDoc -> [SDoc]
forall a. Int -> a -> [a]
replicate (Int
alt Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) SDoc
vbar [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [a -> SDoc
pp a
x] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ Int -> SDoc -> [SDoc]
forall a. Int -> a -> [a]
replicate (Int
arity Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
alt) SDoc
vbar)
data EP a = EP { EP a -> a
fromEP :: a,
EP a -> a
toEP :: a }
data OccInfo
= ManyOccs { OccInfo -> TailCallInfo
occ_tail :: !TailCallInfo }
| IAmDead
| OneOcc { OccInfo -> Bool
occ_in_lam :: !InsideLam
, OccInfo -> Bool
occ_one_br :: !OneBranch
, OccInfo -> Bool
occ_int_cxt :: !InterestingCxt
, occ_tail :: !TailCallInfo }
| IAmALoopBreaker { OccInfo -> Bool
occ_rules_only :: !RulesOnly
, occ_tail :: !TailCallInfo }
deriving (OccInfo -> OccInfo -> Bool
(OccInfo -> OccInfo -> Bool)
-> (OccInfo -> OccInfo -> Bool) -> Eq OccInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OccInfo -> OccInfo -> Bool
$c/= :: OccInfo -> OccInfo -> Bool
== :: OccInfo -> OccInfo -> Bool
$c== :: OccInfo -> OccInfo -> Bool
Eq)
type RulesOnly = Bool
noOccInfo :: OccInfo
noOccInfo :: OccInfo
noOccInfo = ManyOccs :: TailCallInfo -> OccInfo
ManyOccs { occ_tail :: TailCallInfo
occ_tail = TailCallInfo
NoTailCallInfo }
isManyOccs :: OccInfo -> Bool
isManyOccs :: OccInfo -> Bool
isManyOccs ManyOccs{} = Bool
True
isManyOccs OccInfo
_ = Bool
False
seqOccInfo :: OccInfo -> ()
seqOccInfo :: OccInfo -> ()
seqOccInfo OccInfo
occ = OccInfo
occ OccInfo -> () -> ()
`seq` ()
type InterestingCxt = Bool
type InsideLam = Bool
insideLam, notInsideLam :: InsideLam
insideLam :: Bool
insideLam = Bool
True
notInsideLam :: Bool
notInsideLam = Bool
False
type OneBranch = Bool
oneBranch, notOneBranch :: OneBranch
oneBranch :: Bool
oneBranch = Bool
True
notOneBranch :: Bool
notOneBranch = Bool
False
data TailCallInfo = AlwaysTailCalled JoinArity
| NoTailCallInfo
deriving (TailCallInfo -> TailCallInfo -> Bool
(TailCallInfo -> TailCallInfo -> Bool)
-> (TailCallInfo -> TailCallInfo -> Bool) -> Eq TailCallInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TailCallInfo -> TailCallInfo -> Bool
$c/= :: TailCallInfo -> TailCallInfo -> Bool
== :: TailCallInfo -> TailCallInfo -> Bool
$c== :: TailCallInfo -> TailCallInfo -> Bool
Eq)
tailCallInfo :: OccInfo -> TailCallInfo
tailCallInfo :: OccInfo -> TailCallInfo
tailCallInfo OccInfo
IAmDead = TailCallInfo
NoTailCallInfo
tailCallInfo OccInfo
other = OccInfo -> TailCallInfo
occ_tail OccInfo
other
zapOccTailCallInfo :: OccInfo -> OccInfo
zapOccTailCallInfo :: OccInfo -> OccInfo
zapOccTailCallInfo OccInfo
IAmDead = OccInfo
IAmDead
zapOccTailCallInfo OccInfo
occ = OccInfo
occ { occ_tail :: TailCallInfo
occ_tail = TailCallInfo
NoTailCallInfo }
isAlwaysTailCalled :: OccInfo -> Bool
isAlwaysTailCalled :: OccInfo -> Bool
isAlwaysTailCalled OccInfo
occ
= case OccInfo -> TailCallInfo
tailCallInfo OccInfo
occ of AlwaysTailCalled{} -> Bool
True
TailCallInfo
NoTailCallInfo -> Bool
False
instance Outputable TailCallInfo where
ppr :: TailCallInfo -> SDoc
ppr (AlwaysTailCalled Int
ar) = [SDoc] -> SDoc
sep [ String -> SDoc
text String
"Tail", Int -> SDoc
int Int
ar ]
ppr TailCallInfo
_ = SDoc
empty
strongLoopBreaker, weakLoopBreaker :: OccInfo
strongLoopBreaker :: OccInfo
strongLoopBreaker = Bool -> TailCallInfo -> OccInfo
IAmALoopBreaker Bool
False TailCallInfo
NoTailCallInfo
weakLoopBreaker :: OccInfo
weakLoopBreaker = Bool -> TailCallInfo -> OccInfo
IAmALoopBreaker Bool
True TailCallInfo
NoTailCallInfo
isWeakLoopBreaker :: OccInfo -> Bool
isWeakLoopBreaker :: OccInfo -> Bool
isWeakLoopBreaker (IAmALoopBreaker{}) = Bool
True
isWeakLoopBreaker OccInfo
_ = Bool
False
isStrongLoopBreaker :: OccInfo -> Bool
isStrongLoopBreaker :: OccInfo -> Bool
isStrongLoopBreaker (IAmALoopBreaker { occ_rules_only :: OccInfo -> Bool
occ_rules_only = Bool
False }) = Bool
True
isStrongLoopBreaker OccInfo
_ = Bool
False
isDeadOcc :: OccInfo -> Bool
isDeadOcc :: OccInfo -> Bool
isDeadOcc OccInfo
IAmDead = Bool
True
isDeadOcc OccInfo
_ = Bool
False
isOneOcc :: OccInfo -> Bool
isOneOcc :: OccInfo -> Bool
isOneOcc (OneOcc {}) = Bool
True
isOneOcc OccInfo
_ = Bool
False
zapFragileOcc :: OccInfo -> OccInfo
zapFragileOcc :: OccInfo -> OccInfo
zapFragileOcc (OneOcc {}) = OccInfo
noOccInfo
zapFragileOcc OccInfo
occ = OccInfo -> OccInfo
zapOccTailCallInfo OccInfo
occ
instance Outputable OccInfo where
ppr :: OccInfo -> SDoc
ppr (ManyOccs TailCallInfo
tails) = TailCallInfo -> SDoc
pprShortTailCallInfo TailCallInfo
tails
ppr OccInfo
IAmDead = String -> SDoc
text String
"Dead"
ppr (IAmALoopBreaker Bool
rule_only TailCallInfo
tails)
= String -> SDoc
text String
"LoopBreaker" SDoc -> SDoc -> SDoc
<> SDoc
pp_ro SDoc -> SDoc -> SDoc
<> TailCallInfo -> SDoc
pprShortTailCallInfo TailCallInfo
tails
where
pp_ro :: SDoc
pp_ro | Bool
rule_only = Char -> SDoc
char Char
'!'
| Bool
otherwise = SDoc
empty
ppr (OneOcc Bool
inside_lam Bool
one_branch Bool
int_cxt TailCallInfo
tail_info)
= String -> SDoc
text String
"Once" SDoc -> SDoc -> SDoc
<> SDoc
pp_lam SDoc -> SDoc -> SDoc
<> SDoc
pp_br SDoc -> SDoc -> SDoc
<> SDoc
pp_args SDoc -> SDoc -> SDoc
<> SDoc
pp_tail
where
pp_lam :: SDoc
pp_lam | Bool
inside_lam = Char -> SDoc
char Char
'L'
| Bool
otherwise = SDoc
empty
pp_br :: SDoc
pp_br | Bool
one_branch = SDoc
empty
| Bool
otherwise = Char -> SDoc
char Char
'*'
pp_args :: SDoc
pp_args | Bool
int_cxt = Char -> SDoc
char Char
'!'
| Bool
otherwise = SDoc
empty
pp_tail :: SDoc
pp_tail = TailCallInfo -> SDoc
pprShortTailCallInfo TailCallInfo
tail_info
pprShortTailCallInfo :: TailCallInfo -> SDoc
pprShortTailCallInfo :: TailCallInfo -> SDoc
pprShortTailCallInfo (AlwaysTailCalled Int
ar) = Char -> SDoc
char Char
'T' SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
brackets (Int -> SDoc
int Int
ar)
pprShortTailCallInfo TailCallInfo
NoTailCallInfo = SDoc
empty
data DefMethSpec ty
= VanillaDM
| GenericDM ty
instance Outputable (DefMethSpec ty) where
ppr :: DefMethSpec ty -> SDoc
ppr DefMethSpec ty
VanillaDM = String -> SDoc
text String
"{- Has default method -}"
ppr (GenericDM {}) = String -> SDoc
text String
"{- Has generic default method -}"
data SuccessFlag = Succeeded | Failed
instance Outputable SuccessFlag where
ppr :: SuccessFlag -> SDoc
ppr SuccessFlag
Succeeded = String -> SDoc
text String
"Succeeded"
ppr SuccessFlag
Failed = String -> SDoc
text String
"Failed"
successIf :: Bool -> SuccessFlag
successIf :: Bool -> SuccessFlag
successIf Bool
True = SuccessFlag
Succeeded
successIf Bool
False = SuccessFlag
Failed
succeeded, failed :: SuccessFlag -> Bool
succeeded :: SuccessFlag -> Bool
succeeded SuccessFlag
Succeeded = Bool
True
succeeded SuccessFlag
Failed = Bool
False
failed :: SuccessFlag -> Bool
failed SuccessFlag
Succeeded = Bool
False
failed SuccessFlag
Failed = Bool
True
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"
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
type PhaseNum = Int
data CompilerPhase
= Phase PhaseNum
| InitialPhase
instance Outputable CompilerPhase where
ppr :: CompilerPhase -> SDoc
ppr (Phase Int
n) = Int -> SDoc
int Int
n
ppr CompilerPhase
InitialPhase = String -> SDoc
text String
"InitialPhase"
activeAfterInitial :: Activation
activeAfterInitial :: Activation
activeAfterInitial = SourceText -> Int -> Activation
ActiveAfter SourceText
NoSourceText Int
2
activeDuringFinal :: Activation
activeDuringFinal :: Activation
activeDuringFinal = SourceText -> Int -> Activation
ActiveAfter SourceText
NoSourceText Int
0
data Activation = NeverActive
| AlwaysActive
| ActiveBefore SourceText PhaseNum
| ActiveAfter SourceText PhaseNum
deriving( Activation -> Activation -> Bool
(Activation -> Activation -> Bool)
-> (Activation -> Activation -> Bool) -> Eq Activation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Activation -> Activation -> Bool
$c/= :: Activation -> Activation -> Bool
== :: Activation -> Activation -> Bool
$c== :: Activation -> Activation -> Bool
Eq, Typeable Activation
DataType
Constr
Typeable Activation
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation)
-> (Activation -> Constr)
-> (Activation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Activation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Activation))
-> ((forall b. Data b => b -> b) -> Activation -> Activation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r)
-> (forall u. (forall d. Data d => d -> u) -> Activation -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Activation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation)
-> Data Activation
Activation -> DataType
Activation -> Constr
(forall b. Data b => b -> b) -> Activation -> Activation
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation
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) -> Activation -> u
forall u. (forall d. Data d => d -> u) -> Activation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Activation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation)
$cActiveAfter :: Constr
$cActiveBefore :: Constr
$cAlwaysActive :: Constr
$cNeverActive :: Constr
$tActivation :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Activation -> m Activation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
gmapMp :: (forall d. Data d => d -> m d) -> Activation -> m Activation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
gmapM :: (forall d. Data d => d -> m d) -> Activation -> m Activation
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Activation -> u
gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Activation -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation
$cgmapT :: (forall b. Data b => b -> b) -> Activation -> Activation
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Activation)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Activation)
dataTypeOf :: Activation -> DataType
$cdataTypeOf :: Activation -> DataType
toConstr :: Activation -> Constr
$ctoConstr :: Activation -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation
$cp1Data :: Typeable Activation
Data )
data RuleMatchInfo = ConLike
| FunLike
deriving( RuleMatchInfo -> RuleMatchInfo -> Bool
(RuleMatchInfo -> RuleMatchInfo -> Bool)
-> (RuleMatchInfo -> RuleMatchInfo -> Bool) -> Eq RuleMatchInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RuleMatchInfo -> RuleMatchInfo -> Bool
$c/= :: RuleMatchInfo -> RuleMatchInfo -> Bool
== :: RuleMatchInfo -> RuleMatchInfo -> Bool
$c== :: RuleMatchInfo -> RuleMatchInfo -> Bool
Eq, Typeable RuleMatchInfo
DataType
Constr
Typeable RuleMatchInfo
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo)
-> (RuleMatchInfo -> Constr)
-> (RuleMatchInfo -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RuleMatchInfo))
-> ((forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r)
-> (forall u. (forall d. Data d => d -> u) -> RuleMatchInfo -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo)
-> Data RuleMatchInfo
RuleMatchInfo -> DataType
RuleMatchInfo -> Constr
(forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo
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) -> RuleMatchInfo -> u
forall u. (forall d. Data d => d -> u) -> RuleMatchInfo -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RuleMatchInfo)
$cFunLike :: Constr
$cConLike :: Constr
$tRuleMatchInfo :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
gmapMp :: (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
gmapM :: (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u
gmapQ :: (forall d. Data d => d -> u) -> RuleMatchInfo -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RuleMatchInfo -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
gmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo
$cgmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RuleMatchInfo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RuleMatchInfo)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo)
dataTypeOf :: RuleMatchInfo -> DataType
$cdataTypeOf :: RuleMatchInfo -> DataType
toConstr :: RuleMatchInfo -> Constr
$ctoConstr :: RuleMatchInfo -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo
$cp1Data :: Typeable RuleMatchInfo
Data, Int -> RuleMatchInfo -> ShowS
[RuleMatchInfo] -> ShowS
RuleMatchInfo -> String
(Int -> RuleMatchInfo -> ShowS)
-> (RuleMatchInfo -> String)
-> ([RuleMatchInfo] -> ShowS)
-> Show RuleMatchInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RuleMatchInfo] -> ShowS
$cshowList :: [RuleMatchInfo] -> ShowS
show :: RuleMatchInfo -> String
$cshow :: RuleMatchInfo -> String
showsPrec :: Int -> RuleMatchInfo -> ShowS
$cshowsPrec :: Int -> RuleMatchInfo -> ShowS
Show )
data InlinePragma
= InlinePragma
{ InlinePragma -> SourceText
inl_src :: SourceText
, InlinePragma -> InlineSpec
inl_inline :: InlineSpec
, InlinePragma -> Maybe Int
inl_sat :: Maybe Arity
, InlinePragma -> Activation
inl_act :: Activation
, InlinePragma -> RuleMatchInfo
inl_rule :: RuleMatchInfo
} deriving( InlinePragma -> InlinePragma -> Bool
(InlinePragma -> InlinePragma -> Bool)
-> (InlinePragma -> InlinePragma -> Bool) -> Eq InlinePragma
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlinePragma -> InlinePragma -> Bool
$c/= :: InlinePragma -> InlinePragma -> Bool
== :: InlinePragma -> InlinePragma -> Bool
$c== :: InlinePragma -> InlinePragma -> Bool
Eq, Typeable InlinePragma
DataType
Constr
Typeable InlinePragma
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma)
-> (InlinePragma -> Constr)
-> (InlinePragma -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlinePragma))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlinePragma))
-> ((forall b. Data b => b -> b) -> InlinePragma -> InlinePragma)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r)
-> (forall u. (forall d. Data d => d -> u) -> InlinePragma -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> InlinePragma -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma)
-> Data InlinePragma
InlinePragma -> DataType
InlinePragma -> Constr
(forall b. Data b => b -> b) -> InlinePragma -> InlinePragma
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma
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) -> InlinePragma -> u
forall u. (forall d. Data d => d -> u) -> InlinePragma -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlinePragma)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlinePragma)
$cInlinePragma :: Constr
$tInlinePragma :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
gmapMp :: (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
gmapM :: (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InlinePragma -> u
gmapQ :: (forall d. Data d => d -> u) -> InlinePragma -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> InlinePragma -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma
$cgmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlinePragma)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlinePragma)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c InlinePragma)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlinePragma)
dataTypeOf :: InlinePragma -> DataType
$cdataTypeOf :: InlinePragma -> DataType
toConstr :: InlinePragma -> Constr
$ctoConstr :: InlinePragma -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma
$cp1Data :: Typeable InlinePragma
Data )
data InlineSpec
= Inline
| Inlinable
| NoInline
| NoUserInline
deriving( InlineSpec -> InlineSpec -> Bool
(InlineSpec -> InlineSpec -> Bool)
-> (InlineSpec -> InlineSpec -> Bool) -> Eq InlineSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineSpec -> InlineSpec -> Bool
$c/= :: InlineSpec -> InlineSpec -> Bool
== :: InlineSpec -> InlineSpec -> Bool
$c== :: InlineSpec -> InlineSpec -> Bool
Eq, Typeable InlineSpec
DataType
Constr
Typeable InlineSpec
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec)
-> (InlineSpec -> Constr)
-> (InlineSpec -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlineSpec))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlineSpec))
-> ((forall b. Data b => b -> b) -> InlineSpec -> InlineSpec)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r)
-> (forall u. (forall d. Data d => d -> u) -> InlineSpec -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> InlineSpec -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec)
-> Data InlineSpec
InlineSpec -> DataType
InlineSpec -> Constr
(forall b. Data b => b -> b) -> InlineSpec -> InlineSpec
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec
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) -> InlineSpec -> u
forall u. (forall d. Data d => d -> u) -> InlineSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlineSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec)
$cNoUserInline :: Constr
$cNoInline :: Constr
$cInlinable :: Constr
$cInline :: Constr
$tInlineSpec :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
gmapMp :: (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
gmapM :: (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InlineSpec -> u
gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> InlineSpec -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec
$cgmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c InlineSpec)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlineSpec)
dataTypeOf :: InlineSpec -> DataType
$cdataTypeOf :: InlineSpec -> DataType
toConstr :: InlineSpec -> Constr
$ctoConstr :: InlineSpec -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec
$cp1Data :: Typeable InlineSpec
Data, Int -> InlineSpec -> ShowS
[InlineSpec] -> ShowS
InlineSpec -> String
(Int -> InlineSpec -> ShowS)
-> (InlineSpec -> String)
-> ([InlineSpec] -> ShowS)
-> Show InlineSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineSpec] -> ShowS
$cshowList :: [InlineSpec] -> ShowS
show :: InlineSpec -> String
$cshow :: InlineSpec -> String
showsPrec :: Int -> InlineSpec -> ShowS
$cshowsPrec :: Int -> InlineSpec -> ShowS
Show )
isConLike :: RuleMatchInfo -> Bool
isConLike :: RuleMatchInfo -> Bool
isConLike RuleMatchInfo
ConLike = Bool
True
isConLike RuleMatchInfo
_ = Bool
False
isFunLike :: RuleMatchInfo -> Bool
isFunLike :: RuleMatchInfo -> Bool
isFunLike RuleMatchInfo
FunLike = Bool
True
isFunLike RuleMatchInfo
_ = Bool
False
noUserInlineSpec :: InlineSpec -> Bool
noUserInlineSpec :: InlineSpec -> Bool
noUserInlineSpec InlineSpec
NoUserInline = Bool
True
noUserInlineSpec InlineSpec
_ = Bool
False
defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma
:: InlinePragma
defaultInlinePragma :: InlinePragma
defaultInlinePragma = InlinePragma :: SourceText
-> InlineSpec
-> Maybe Int
-> Activation
-> RuleMatchInfo
-> InlinePragma
InlinePragma { inl_src :: SourceText
inl_src = String -> SourceText
SourceText String
"{-# INLINE"
, inl_act :: Activation
inl_act = Activation
AlwaysActive
, inl_rule :: RuleMatchInfo
inl_rule = RuleMatchInfo
FunLike
, inl_inline :: InlineSpec
inl_inline = InlineSpec
NoUserInline
, inl_sat :: Maybe Int
inl_sat = Maybe Int
forall a. Maybe a
Nothing }
alwaysInlinePragma :: InlinePragma
alwaysInlinePragma = InlinePragma
defaultInlinePragma { inl_inline :: InlineSpec
inl_inline = InlineSpec
Inline }
neverInlinePragma :: InlinePragma
neverInlinePragma = InlinePragma
defaultInlinePragma { inl_act :: Activation
inl_act = Activation
NeverActive }
inlinePragmaSpec :: InlinePragma -> InlineSpec
inlinePragmaSpec :: InlinePragma -> InlineSpec
inlinePragmaSpec = InlinePragma -> InlineSpec
inl_inline
dfunInlinePragma :: InlinePragma
dfunInlinePragma = InlinePragma
defaultInlinePragma { inl_act :: Activation
inl_act = Activation
AlwaysActive
, inl_rule :: RuleMatchInfo
inl_rule = RuleMatchInfo
ConLike }
isDefaultInlinePragma :: InlinePragma -> Bool
isDefaultInlinePragma :: InlinePragma -> Bool
isDefaultInlinePragma (InlinePragma { inl_act :: InlinePragma -> Activation
inl_act = Activation
activation
, inl_rule :: InlinePragma -> RuleMatchInfo
inl_rule = RuleMatchInfo
match_info
, inl_inline :: InlinePragma -> InlineSpec
inl_inline = InlineSpec
inline })
= InlineSpec -> Bool
noUserInlineSpec InlineSpec
inline Bool -> Bool -> Bool
&& Activation -> Bool
isAlwaysActive Activation
activation Bool -> Bool -> Bool
&& RuleMatchInfo -> Bool
isFunLike RuleMatchInfo
match_info
isInlinePragma :: InlinePragma -> Bool
isInlinePragma :: InlinePragma -> Bool
isInlinePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
InlineSpec
Inline -> Bool
True
InlineSpec
_ -> Bool
False
isInlinablePragma :: InlinePragma -> Bool
isInlinablePragma :: InlinePragma -> Bool
isInlinablePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
InlineSpec
Inlinable -> Bool
True
InlineSpec
_ -> Bool
False
isAnyInlinePragma :: InlinePragma -> Bool
isAnyInlinePragma :: InlinePragma -> Bool
isAnyInlinePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
InlineSpec
Inline -> Bool
True
InlineSpec
Inlinable -> Bool
True
InlineSpec
_ -> Bool
False
inlinePragmaSat :: InlinePragma -> Maybe Arity
inlinePragmaSat :: InlinePragma -> Maybe Int
inlinePragmaSat = InlinePragma -> Maybe Int
inl_sat
inlinePragmaActivation :: InlinePragma -> Activation
inlinePragmaActivation :: InlinePragma -> Activation
inlinePragmaActivation (InlinePragma { inl_act :: InlinePragma -> Activation
inl_act = Activation
activation }) = Activation
activation
inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
inlinePragmaRuleMatchInfo (InlinePragma { inl_rule :: InlinePragma -> RuleMatchInfo
inl_rule = RuleMatchInfo
info }) = RuleMatchInfo
info
setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
setInlinePragmaActivation InlinePragma
prag Activation
activation = InlinePragma
prag { inl_act :: Activation
inl_act = Activation
activation }
setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
setInlinePragmaRuleMatchInfo InlinePragma
prag RuleMatchInfo
info = InlinePragma
prag { inl_rule :: RuleMatchInfo
inl_rule = RuleMatchInfo
info }
instance Outputable Activation where
ppr :: Activation -> SDoc
ppr Activation
AlwaysActive = SDoc
empty
ppr Activation
NeverActive = SDoc -> SDoc
brackets (String -> SDoc
text String
"~")
ppr (ActiveBefore SourceText
_ Int
n) = SDoc -> SDoc
brackets (Char -> SDoc
char Char
'~' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
n)
ppr (ActiveAfter SourceText
_ Int
n) = SDoc -> SDoc
brackets (Int -> SDoc
int Int
n)
instance Outputable RuleMatchInfo where
ppr :: RuleMatchInfo -> SDoc
ppr RuleMatchInfo
ConLike = String -> SDoc
text String
"CONLIKE"
ppr RuleMatchInfo
FunLike = String -> SDoc
text String
"FUNLIKE"
instance Outputable InlineSpec where
ppr :: InlineSpec -> SDoc
ppr InlineSpec
Inline = String -> SDoc
text String
"INLINE"
ppr InlineSpec
NoInline = String -> SDoc
text String
"NOINLINE"
ppr InlineSpec
Inlinable = String -> SDoc
text String
"INLINABLE"
ppr InlineSpec
NoUserInline = String -> SDoc
text String
"NOUSERINLINE"
instance Outputable InlinePragma where
ppr :: InlinePragma -> SDoc
ppr = InlinePragma -> SDoc
pprInline
pprInline :: InlinePragma -> SDoc
pprInline :: InlinePragma -> SDoc
pprInline = Bool -> InlinePragma -> SDoc
pprInline' Bool
True
pprInlineDebug :: InlinePragma -> SDoc
pprInlineDebug :: InlinePragma -> SDoc
pprInlineDebug = Bool -> InlinePragma -> SDoc
pprInline' Bool
False
pprInline' :: Bool
-> InlinePragma
-> SDoc
pprInline' :: Bool -> InlinePragma -> SDoc
pprInline' Bool
emptyInline (InlinePragma { inl_inline :: InlinePragma -> InlineSpec
inl_inline = InlineSpec
inline, inl_act :: InlinePragma -> Activation
inl_act = Activation
activation
, inl_rule :: InlinePragma -> RuleMatchInfo
inl_rule = RuleMatchInfo
info, inl_sat :: InlinePragma -> Maybe Int
inl_sat = Maybe Int
mb_arity })
= InlineSpec -> SDoc
forall a. Outputable a => a -> SDoc
pp_inl InlineSpec
inline SDoc -> SDoc -> SDoc
<> InlineSpec -> Activation -> SDoc
pp_act InlineSpec
inline Activation
activation SDoc -> SDoc -> SDoc
<+> SDoc
pp_sat SDoc -> SDoc -> SDoc
<+> SDoc
pp_info
where
pp_inl :: a -> SDoc
pp_inl a
x = if Bool
emptyInline then SDoc
empty else a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
x
pp_act :: InlineSpec -> Activation -> SDoc
pp_act InlineSpec
Inline Activation
AlwaysActive = SDoc
empty
pp_act InlineSpec
NoInline Activation
NeverActive = SDoc
empty
pp_act InlineSpec
_ Activation
act = Activation -> SDoc
forall a. Outputable a => a -> SDoc
ppr Activation
act
pp_sat :: SDoc
pp_sat | Just Int
ar <- Maybe Int
mb_arity = SDoc -> SDoc
parens (String -> SDoc
text String
"sat-args=" SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
ar)
| Bool
otherwise = SDoc
empty
pp_info :: SDoc
pp_info | RuleMatchInfo -> Bool
isFunLike RuleMatchInfo
info = SDoc
empty
| Bool
otherwise = RuleMatchInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr RuleMatchInfo
info
isActive :: CompilerPhase -> Activation -> Bool
isActive :: CompilerPhase -> Activation -> Bool
isActive CompilerPhase
InitialPhase Activation
AlwaysActive = Bool
True
isActive CompilerPhase
InitialPhase (ActiveBefore {}) = Bool
True
isActive CompilerPhase
InitialPhase Activation
_ = Bool
False
isActive (Phase Int
p) Activation
act = Int -> Activation -> Bool
isActiveIn Int
p Activation
act
isActiveIn :: PhaseNum -> Activation -> Bool
isActiveIn :: Int -> Activation -> Bool
isActiveIn Int
_ Activation
NeverActive = Bool
False
isActiveIn Int
_ Activation
AlwaysActive = Bool
True
isActiveIn Int
p (ActiveAfter SourceText
_ Int
n) = Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n
isActiveIn Int
p (ActiveBefore SourceText
_ Int
n) = Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n
competesWith :: Activation -> Activation -> Bool
competesWith :: Activation -> Activation -> Bool
competesWith Activation
NeverActive Activation
_ = Bool
False
competesWith Activation
_ Activation
NeverActive = Bool
False
competesWith Activation
AlwaysActive Activation
_ = Bool
True
competesWith (ActiveBefore {}) Activation
AlwaysActive = Bool
True
competesWith (ActiveBefore {}) (ActiveBefore {}) = Bool
True
competesWith (ActiveBefore SourceText
_ Int
a) (ActiveAfter SourceText
_ Int
b) = Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
b
competesWith (ActiveAfter {}) Activation
AlwaysActive = Bool
False
competesWith (ActiveAfter {}) (ActiveBefore {}) = Bool
False
competesWith (ActiveAfter SourceText
_ Int
a) (ActiveAfter SourceText
_ Int
b) = Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
b
isNeverActive, isAlwaysActive, isEarlyActive :: Activation -> Bool
isNeverActive :: Activation -> Bool
isNeverActive Activation
NeverActive = Bool
True
isNeverActive Activation
_ = Bool
False
isAlwaysActive :: Activation -> Bool
isAlwaysActive Activation
AlwaysActive = Bool
True
isAlwaysActive Activation
_ = Bool
False
isEarlyActive :: Activation -> Bool
isEarlyActive Activation
AlwaysActive = Bool
True
isEarlyActive (ActiveBefore {}) = Bool
True
isEarlyActive Activation
_ = Bool
False
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_value :: Rational
}
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)
mkFractionalLit :: Real a => a -> FractionalLit
mkFractionalLit :: a -> FractionalLit
mkFractionalLit a
r = FL :: SourceText -> Bool -> Rational -> FractionalLit
FL { fl_text :: SourceText
fl_text = String -> SourceText
SourceText (Double -> String
forall a. Show a => a -> String
show (a -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
r::Double))
, fl_neg :: Bool
fl_neg = a
r a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0
, fl_value :: Rational
fl_value = a -> Rational
forall a. Real a => a -> Rational
toRational a
r }
negateFractionalLit :: FractionalLit -> FractionalLit
negateFractionalLit :: FractionalLit -> FractionalLit
negateFractionalLit (FL SourceText
text Bool
neg Rational
value)
= case SourceText
text of
SourceText (Char
'-':String
src) -> SourceText -> Bool -> Rational -> FractionalLit
FL (String -> SourceText
SourceText String
src) Bool
False Rational
value
SourceText String
src -> SourceText -> Bool -> Rational -> FractionalLit
FL (String -> SourceText
SourceText (Char
'-'Char -> ShowS
forall a. a -> [a] -> [a]
:String
src)) Bool
True Rational
value
SourceText
NoSourceText -> SourceText -> Bool -> Rational -> FractionalLit
FL SourceText
NoSourceText (Bool -> Bool
not Bool
neg) (Rational -> Rational
forall a. Num a => a -> a
negate Rational
value)
integralFractionalLit :: Bool -> Integer -> FractionalLit
integralFractionalLit :: Bool -> Integer -> FractionalLit
integralFractionalLit Bool
neg Integer
i = FL :: SourceText -> Bool -> Rational -> 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_value :: Rational
fl_value = Integer -> Rational
forall a. Num a => Integer -> a
fromInteger Integer
i }
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)
instance Eq FractionalLit where
== :: FractionalLit -> FractionalLit -> Bool
(==) = Rational -> Rational -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Rational -> Rational -> Bool)
-> (FractionalLit -> Rational)
-> FractionalLit
-> FractionalLit
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` FractionalLit -> Rational
fl_value
instance Ord FractionalLit where
compare :: FractionalLit -> FractionalLit -> Ordering
compare = Rational -> Rational -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Rational -> Rational -> Ordering)
-> (FractionalLit -> Rational)
-> FractionalLit
-> FractionalLit
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` FractionalLit -> Rational
fl_value
instance Outputable FractionalLit where
ppr :: FractionalLit -> SDoc
ppr FractionalLit
f = SourceText -> SDoc -> SDoc
pprWithSourceText (FractionalLit -> SourceText
fl_text FractionalLit
f) (Rational -> SDoc
rational (FractionalLit -> Rational
fl_value FractionalLit
f))
data IntWithInf = Int {-# UNPACK #-} !Int
| Infinity
deriving IntWithInf -> IntWithInf -> Bool
(IntWithInf -> IntWithInf -> Bool)
-> (IntWithInf -> IntWithInf -> Bool) -> Eq IntWithInf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntWithInf -> IntWithInf -> Bool
$c/= :: IntWithInf -> IntWithInf -> Bool
== :: IntWithInf -> IntWithInf -> Bool
$c== :: IntWithInf -> IntWithInf -> Bool
Eq
infinity :: IntWithInf
infinity :: IntWithInf
infinity = IntWithInf
Infinity
instance Ord IntWithInf where
compare :: IntWithInf -> IntWithInf -> Ordering
compare IntWithInf
Infinity IntWithInf
Infinity = Ordering
EQ
compare (Int Int
_) IntWithInf
Infinity = Ordering
LT
compare IntWithInf
Infinity (Int Int
_) = Ordering
GT
compare (Int Int
a) (Int Int
b) = Int
a Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Int
b
instance Outputable IntWithInf where
ppr :: IntWithInf -> SDoc
ppr IntWithInf
Infinity = Char -> SDoc
char Char
'∞'
ppr (Int Int
n) = Int -> SDoc
int Int
n
instance Num IntWithInf where
+ :: IntWithInf -> IntWithInf -> IntWithInf
(+) = IntWithInf -> IntWithInf -> IntWithInf
plusWithInf
* :: IntWithInf -> IntWithInf -> IntWithInf
(*) = IntWithInf -> IntWithInf -> IntWithInf
mulWithInf
abs :: IntWithInf -> IntWithInf
abs IntWithInf
Infinity = IntWithInf
Infinity
abs (Int Int
n) = Int -> IntWithInf
Int (Int -> Int
forall a. Num a => a -> a
abs Int
n)
signum :: IntWithInf -> IntWithInf
signum IntWithInf
Infinity = Int -> IntWithInf
Int Int
1
signum (Int Int
n) = Int -> IntWithInf
Int (Int -> Int
forall a. Num a => a -> a
signum Int
n)
fromInteger :: Integer -> IntWithInf
fromInteger = Int -> IntWithInf
Int (Int -> IntWithInf) -> (Integer -> Int) -> Integer -> IntWithInf
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
(-) = String -> IntWithInf -> IntWithInf -> IntWithInf
forall a. String -> a
panic String
"subtracting IntWithInfs"
intGtLimit :: Int -> IntWithInf -> Bool
intGtLimit :: Int -> IntWithInf -> Bool
intGtLimit Int
_ IntWithInf
Infinity = Bool
False
intGtLimit Int
n (Int Int
m) = Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
m
plusWithInf :: IntWithInf -> IntWithInf -> IntWithInf
plusWithInf :: IntWithInf -> IntWithInf -> IntWithInf
plusWithInf IntWithInf
Infinity IntWithInf
_ = IntWithInf
Infinity
plusWithInf IntWithInf
_ IntWithInf
Infinity = IntWithInf
Infinity
plusWithInf (Int Int
a) (Int Int
b) = Int -> IntWithInf
Int (Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
b)
mulWithInf :: IntWithInf -> IntWithInf -> IntWithInf
mulWithInf :: IntWithInf -> IntWithInf -> IntWithInf
mulWithInf IntWithInf
Infinity IntWithInf
_ = IntWithInf
Infinity
mulWithInf IntWithInf
_ IntWithInf
Infinity = IntWithInf
Infinity
mulWithInf (Int Int
a) (Int Int
b) = Int -> IntWithInf
Int (Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
b)
treatZeroAsInf :: Int -> IntWithInf
treatZeroAsInf :: Int -> IntWithInf
treatZeroAsInf Int
0 = IntWithInf
Infinity
treatZeroAsInf Int
n = Int -> IntWithInf
Int Int
n
mkIntWithInf :: Int -> IntWithInf
mkIntWithInf :: Int -> IntWithInf
mkIntWithInf = Int -> IntWithInf
Int
data SpliceExplicitFlag
= ExplicitSplice |
ImplicitSplice
deriving Typeable SpliceExplicitFlag
DataType
Constr
Typeable SpliceExplicitFlag
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpliceExplicitFlag
-> c SpliceExplicitFlag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag)
-> (SpliceExplicitFlag -> Constr)
-> (SpliceExplicitFlag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpliceExplicitFlag))
-> ((forall b. Data b => b -> b)
-> SpliceExplicitFlag -> SpliceExplicitFlag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r)
-> (forall u.
(forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag)
-> Data SpliceExplicitFlag
SpliceExplicitFlag -> DataType
SpliceExplicitFlag -> Constr
(forall b. Data b => b -> b)
-> SpliceExplicitFlag -> SpliceExplicitFlag
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpliceExplicitFlag
-> c SpliceExplicitFlag
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag
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) -> SpliceExplicitFlag -> u
forall u. (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpliceExplicitFlag
-> c SpliceExplicitFlag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpliceExplicitFlag)
$cImplicitSplice :: Constr
$cExplicitSplice :: Constr
$tSpliceExplicitFlag :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
gmapMp :: (forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
gmapM :: (forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SpliceExplicitFlag -> m SpliceExplicitFlag
gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u
gmapQ :: (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r
gmapT :: (forall b. Data b => b -> b)
-> SpliceExplicitFlag -> SpliceExplicitFlag
$cgmapT :: (forall b. Data b => b -> b)
-> SpliceExplicitFlag -> SpliceExplicitFlag
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpliceExplicitFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SpliceExplicitFlag)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag)
dataTypeOf :: SpliceExplicitFlag -> DataType
$cdataTypeOf :: SpliceExplicitFlag -> DataType
toConstr :: SpliceExplicitFlag -> Constr
$ctoConstr :: SpliceExplicitFlag -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpliceExplicitFlag
-> c SpliceExplicitFlag
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> SpliceExplicitFlag
-> c SpliceExplicitFlag
$cp1Data :: Typeable SpliceExplicitFlag
Data