{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
module GHC.Types.Basic (
LeftOrRight(..),
pickLR,
ConTag, ConTagZ, fIRST_TAG,
Arity, RepArity, JoinArity, FullArgCount,
Alignment, mkAlignment, alignmentOf, alignmentBytes,
PromotionFlag(..), isPromoted,
FunctionOrData(..),
RecFlag(..), isRec, isNonRec, boolToRecFlag,
Origin(..), isGenerated,
RuleName, pprRuleName,
TopLevelFlag(..), isTopLevel, isNotTopLevel,
OverlapFlag(..), OverlapMode(..), setOverlapModeMaybe,
hasOverlappingFlag, hasOverlappableFlag, hasIncoherentFlag,
Boxity(..), isBoxed,
CbvMark(..), isMarkedCbv,
PprPrec(..), topPrec, sigPrec, opPrec, funPrec,
starPrec, appPrec, maxPrec,
maybeParen,
TupleSort(..), tupleSortBoxity, boxityTupleSort,
tupleParens,
UnboxedTupleOrSum(..), unboxedTupleOrSumExtension,
sumParens, pprAlternative,
OneShotInfo(..),
noOneShotInfo, hasNoOneShotInfo, isOneShotInfo,
bestOneShot, worstOneShot,
OccInfo(..), noOccInfo, seqOccInfo, zapFragileOcc, isOneOcc,
isDeadOcc, isStrongLoopBreaker, isWeakLoopBreaker, isManyOccs,
isNoOccInfo, strongLoopBreaker, weakLoopBreaker,
InsideLam(..),
BranchCount, oneBranch,
InterestingCxt(..),
TailCallInfo(..), tailCallInfo, zapOccTailCallInfo,
isAlwaysTailCalled,
EP(..),
DefMethSpec(..),
SwapFlag(..), flipSwap, unSwap, isSwapped,
CompilerPhase(..), PhaseNum, beginPhase, nextPhase, laterPhase,
Activation(..), isActive, competesWith,
isNeverActive, isAlwaysActive, activeInFinalPhase,
activateAfterInitial, activateDuringFinal, activeAfter,
RuleMatchInfo(..), isConLike, isFunLike,
InlineSpec(..), noUserInlineSpec,
InlinePragma(..), defaultInlinePragma, alwaysInlinePragma,
neverInlinePragma, dfunInlinePragma,
isDefaultInlinePragma,
isInlinePragma, isInlinablePragma, isNoInlinePragma, isOpaquePragma,
isAnyInlinePragma, alwaysInlineConLikePragma,
inlinePragmaSource,
inlinePragmaName, inlineSpecSource,
inlinePragmaSpec, inlinePragmaSat,
inlinePragmaActivation, inlinePragmaRuleMatchInfo,
setInlinePragmaActivation, setInlinePragmaRuleMatchInfo,
pprInline, pprInlineDebug,
UnfoldingSource(..), isStableSource, isStableUserSource,
isStableSystemSource, isCompulsorySource,
SuccessFlag(..), succeeded, failed, successIf,
IntWithInf, infinity, treatZeroAsInf, subWithInf, mkIntWithInf, intGtLimit,
TypeOrKind(..), isTypeLevel, isKindLevel,
Levity(..), mightBeLifted, mightBeUnlifted,
TypeOrConstraint(..),
NonStandardDefaultingStrategy(..),
DefaultingStrategy(..), defaultNonStandardTyVars,
ForeignSrcLang (..)
) where
import GHC.Prelude
import GHC.ForeignSrcLang
import GHC.Data.FastString
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Binary
import GHC.Types.SourceText
import qualified GHC.LanguageExtensions as LangExt
import Data.Data
import qualified Data.Semigroup as Semi
import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted)
import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag)
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
$c== :: LeftOrRight -> LeftOrRight -> Bool
== :: LeftOrRight -> LeftOrRight -> Bool
$c/= :: LeftOrRight -> LeftOrRight -> Bool
/= :: LeftOrRight -> LeftOrRight -> Bool
Eq, Typeable LeftOrRight
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 -> Constr
LeftOrRight -> DataType
(forall b. Data b => b -> b) -> LeftOrRight -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LeftOrRight
$ctoConstr :: LeftOrRight -> Constr
toConstr :: LeftOrRight -> Constr
$cdataTypeOf :: LeftOrRight -> DataType
dataTypeOf :: LeftOrRight -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LeftOrRight)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LeftOrRight)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LeftOrRight)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c LeftOrRight)
$cgmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight
gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LeftOrRight -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> LeftOrRight -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight
Data )
pickLR :: LeftOrRight -> (a,a) -> a
pickLR :: forall a. 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
forall doc. IsLine doc => String -> doc
text String
"Left"
ppr LeftOrRight
CRight = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Right"
instance Binary LeftOrRight where
put_ :: BinHandle -> LeftOrRight -> IO ()
put_ BinHandle
bh LeftOrRight
CLeft = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh LeftOrRight
CRight = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO LeftOrRight
get BinHandle
bh = do { Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
; case Word8
h of
Word8
0 -> LeftOrRight -> IO LeftOrRight
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LeftOrRight
CLeft
Word8
_ -> LeftOrRight -> IO LeftOrRight
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LeftOrRight
CRight }
type Arity = Int
type RepArity = Int
type JoinArity = Int
type FullArgCount = Int
type ConTagZ = Int
fIRST_TAG :: ConTag
fIRST_TAG :: Int
fIRST_TAG = Int
1
newtype Alignment = Alignment { Alignment -> Int
alignmentBytes :: Int } deriving (Alignment -> Alignment -> Bool
(Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool) -> Eq Alignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Alignment -> Alignment -> Bool
== :: Alignment -> Alignment -> Bool
$c/= :: Alignment -> Alignment -> Bool
/= :: Alignment -> Alignment -> Bool
Eq, Eq Alignment
Eq Alignment =>
(Alignment -> Alignment -> Ordering)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Alignment)
-> (Alignment -> Alignment -> Alignment)
-> Ord Alignment
Alignment -> Alignment -> Bool
Alignment -> Alignment -> Ordering
Alignment -> Alignment -> Alignment
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
$ccompare :: Alignment -> Alignment -> Ordering
compare :: Alignment -> Alignment -> Ordering
$c< :: Alignment -> Alignment -> Bool
< :: Alignment -> Alignment -> Bool
$c<= :: Alignment -> Alignment -> Bool
<= :: Alignment -> Alignment -> Bool
$c> :: Alignment -> Alignment -> Bool
> :: Alignment -> Alignment -> Bool
$c>= :: Alignment -> Alignment -> Bool
>= :: Alignment -> Alignment -> Bool
$cmax :: Alignment -> Alignment -> Alignment
max :: Alignment -> Alignment -> Alignment
$cmin :: Alignment -> Alignment -> Alignment
min :: Alignment -> Alignment -> Alignment
Ord)
mkAlignment :: Int -> Alignment
mkAlignment :: Int -> Alignment
mkAlignment Int
n
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Int -> Alignment
Alignment Int
1
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 = Int -> Alignment
Alignment Int
2
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 = Int -> Alignment
Alignment Int
4
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
8 = Int -> Alignment
Alignment Int
8
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
16 = Int -> Alignment
Alignment Int
16
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
32 = Int -> Alignment
Alignment Int
32
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
64 = Int -> Alignment
Alignment Int
64
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
128 = Int -> Alignment
Alignment Int
128
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
256 = Int -> Alignment
Alignment Int
256
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
512 = Int -> Alignment
Alignment Int
512
| Bool
otherwise = String -> Alignment
forall a. HasCallStack => String -> a
panic String
"mkAlignment: received either a non power of 2 argument or > 512"
alignmentOf :: Int -> Alignment
alignmentOf :: Int -> Alignment
alignmentOf Int
x = case Int
x Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
7 of
Int
0 -> Int -> Alignment
Alignment Int
8
Int
4 -> Int -> Alignment
Alignment Int
4
Int
2 -> Int -> Alignment
Alignment Int
2
Int
_ -> Int -> Alignment
Alignment Int
1
instance Outputable Alignment where
ppr :: Alignment -> SDoc
ppr (Alignment Int
m) = Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
m
instance OutputableP env Alignment where
pdoc :: env -> Alignment -> SDoc
pdoc env
_ = Alignment -> SDoc
forall a. Outputable a => a -> SDoc
ppr
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
$c== :: OneShotInfo -> OneShotInfo -> Bool
== :: OneShotInfo -> OneShotInfo -> Bool
$c/= :: OneShotInfo -> OneShotInfo -> Bool
/= :: 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 = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NoOS"
pprOneShotInfo OneShotInfo
OneShotLam = String -> SDoc
forall doc. IsLine doc => String -> doc
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
forall doc. IsLine doc => String -> doc
text String
"Is-swapped"
ppr SwapFlag
NotSwapped = String -> SDoc
forall doc. IsLine doc => String -> doc
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 :: forall a b. 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
instance Outputable PromotionFlag where
ppr :: PromotionFlag -> SDoc
ppr PromotionFlag
NotPromoted = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NotPromoted"
ppr PromotionFlag
IsPromoted = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"IsPromoted"
instance Binary PromotionFlag where
put_ :: BinHandle -> PromotionFlag -> IO ()
put_ BinHandle
bh PromotionFlag
NotPromoted = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh PromotionFlag
IsPromoted = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO PromotionFlag
get BinHandle
bh = do
Word8
n <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
n of
Word8
0 -> PromotionFlag -> IO PromotionFlag
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PromotionFlag
NotPromoted
Word8
1 -> PromotionFlag -> IO PromotionFlag
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PromotionFlag
IsPromoted
Word8
_ -> String -> IO PromotionFlag
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary(IsPromoted): fail)"
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
$c== :: FunctionOrData -> FunctionOrData -> Bool
== :: FunctionOrData -> FunctionOrData -> Bool
$c/= :: FunctionOrData -> FunctionOrData -> Bool
/= :: 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
$ccompare :: FunctionOrData -> FunctionOrData -> Ordering
compare :: FunctionOrData -> FunctionOrData -> Ordering
$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
>= :: FunctionOrData -> FunctionOrData -> Bool
$cmax :: FunctionOrData -> FunctionOrData -> FunctionOrData
max :: FunctionOrData -> FunctionOrData -> FunctionOrData
$cmin :: FunctionOrData -> FunctionOrData -> FunctionOrData
min :: FunctionOrData -> FunctionOrData -> FunctionOrData
Ord, Typeable FunctionOrData
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 -> Constr
FunctionOrData -> DataType
(forall b. Data b => b -> b) -> FunctionOrData -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FunctionOrData
$ctoConstr :: FunctionOrData -> Constr
toConstr :: FunctionOrData -> Constr
$cdataTypeOf :: FunctionOrData -> DataType
dataTypeOf :: FunctionOrData -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionOrData)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FunctionOrData)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionOrData)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FunctionOrData)
$cgmapT :: (forall b. Data b => b -> b) -> FunctionOrData -> FunctionOrData
gmapT :: (forall b. Data b => b -> b) -> FunctionOrData -> FunctionOrData
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FunctionOrData -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> FunctionOrData -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FunctionOrData -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> FunctionOrData -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> FunctionOrData -> m FunctionOrData
Data)
instance Outputable FunctionOrData where
ppr :: FunctionOrData -> SDoc
ppr FunctionOrData
IsFunction = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(function)"
ppr FunctionOrData
IsData = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(data)"
instance Binary FunctionOrData where
put_ :: BinHandle -> FunctionOrData -> IO ()
put_ BinHandle
bh FunctionOrData
IsFunction = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh FunctionOrData
IsData = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO FunctionOrData
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> FunctionOrData -> IO FunctionOrData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionOrData
IsFunction
Word8
1 -> FunctionOrData -> IO FunctionOrData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunctionOrData
IsData
Word8
_ -> String -> IO FunctionOrData
forall a. HasCallStack => String -> a
panic String
"Binary FunctionOrData"
type RuleName = FastString
pprRuleName :: RuleName -> SDoc
pprRuleName :: RuleName -> SDoc
pprRuleName RuleName
rn = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
doubleQuotes (RuleName -> SDoc
forall doc. IsLine doc => RuleName -> doc
ftext RuleName
rn)
data TopLevelFlag
= TopLevel
| NotTopLevel
deriving Typeable TopLevelFlag
Typeable TopLevelFlag =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelFlag -> c TopLevelFlag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelFlag)
-> (TopLevelFlag -> Constr)
-> (TopLevelFlag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelFlag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelFlag))
-> ((forall b. Data b => b -> b) -> TopLevelFlag -> TopLevelFlag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r)
-> (forall u. (forall d. Data d => d -> u) -> TopLevelFlag -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TopLevelFlag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag)
-> Data TopLevelFlag
TopLevelFlag -> Constr
TopLevelFlag -> DataType
(forall b. Data b => b -> b) -> TopLevelFlag -> TopLevelFlag
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) -> TopLevelFlag -> u
forall u. (forall d. Data d => d -> u) -> TopLevelFlag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelFlag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelFlag -> c TopLevelFlag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelFlag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelFlag)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelFlag -> c TopLevelFlag
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TopLevelFlag -> c TopLevelFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelFlag
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TopLevelFlag
$ctoConstr :: TopLevelFlag -> Constr
toConstr :: TopLevelFlag -> Constr
$cdataTypeOf :: TopLevelFlag -> DataType
dataTypeOf :: TopLevelFlag -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelFlag)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TopLevelFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelFlag)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TopLevelFlag)
$cgmapT :: (forall b. Data b => b -> b) -> TopLevelFlag -> TopLevelFlag
gmapT :: (forall b. Data b => b -> b) -> TopLevelFlag -> TopLevelFlag
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TopLevelFlag -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TopLevelFlag -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TopLevelFlag -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TopLevelFlag -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag
Data
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
forall doc. IsLine doc => String -> doc
text String
"<TopLevel>"
ppr TopLevelFlag
NotTopLevel = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"<NotTopLevel>"
instance Outputable Boxity where
ppr :: Boxity -> SDoc
ppr Boxity
Boxed = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Boxed"
ppr Boxity
Unboxed = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Unboxed"
instance Binary Boxity where
put_ :: BinHandle -> Boxity -> IO ()
put_ BinHandle
bh = BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (Bool -> IO ()) -> (Boxity -> Bool) -> Boxity -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Boxity -> Bool
isBoxed
get :: BinHandle -> IO Boxity
get BinHandle
bh = do
Bool
b <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Boxity -> IO Boxity
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Boxity -> IO Boxity) -> Boxity -> IO Boxity
forall a b. (a -> b) -> a -> b
$ if Bool
b then Boxity
Boxed else Boxity
Unboxed
data CbvMark = MarkedCbv | NotMarkedCbv
deriving CbvMark -> CbvMark -> Bool
(CbvMark -> CbvMark -> Bool)
-> (CbvMark -> CbvMark -> Bool) -> Eq CbvMark
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CbvMark -> CbvMark -> Bool
== :: CbvMark -> CbvMark -> Bool
$c/= :: CbvMark -> CbvMark -> Bool
/= :: CbvMark -> CbvMark -> Bool
Eq
instance Outputable CbvMark where
ppr :: CbvMark -> SDoc
ppr CbvMark
MarkedCbv = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"!"
ppr CbvMark
NotMarkedCbv = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"~"
instance Binary CbvMark where
put_ :: BinHandle -> CbvMark -> IO ()
put_ BinHandle
bh CbvMark
NotMarkedCbv = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh CbvMark
MarkedCbv = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO CbvMark
get BinHandle
bh =
do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> CbvMark -> IO CbvMark
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CbvMark
NotMarkedCbv
Word8
1 -> CbvMark -> IO CbvMark
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CbvMark
MarkedCbv
Word8
_ -> String -> IO CbvMark
forall a. HasCallStack => String -> a
panic String
"Invalid binary format"
isMarkedCbv :: CbvMark -> Bool
isMarkedCbv :: CbvMark -> Bool
isMarkedCbv CbvMark
MarkedCbv = Bool
True
isMarkedCbv CbvMark
NotMarkedCbv = Bool
False
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
$c== :: RecFlag -> RecFlag -> Bool
== :: RecFlag -> RecFlag -> Bool
$c/= :: RecFlag -> RecFlag -> Bool
/= :: RecFlag -> RecFlag -> Bool
Eq, Typeable RecFlag
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 -> Constr
RecFlag -> DataType
(forall b. Data b => b -> b) -> RecFlag -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RecFlag -> c RecFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RecFlag
$ctoConstr :: RecFlag -> Constr
toConstr :: RecFlag -> Constr
$cdataTypeOf :: RecFlag -> DataType
dataTypeOf :: RecFlag -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecFlag)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RecFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag)
$cgmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag
gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RecFlag -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RecFlag -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RecFlag -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RecFlag -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RecFlag -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RecFlag -> m RecFlag
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RecFlag -> m 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
forall doc. IsLine doc => String -> doc
text String
"Recursive"
ppr RecFlag
NonRecursive = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NonRecursive"
instance Binary RecFlag where
put_ :: BinHandle -> RecFlag -> IO ()
put_ BinHandle
bh RecFlag
Recursive =
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh RecFlag
NonRecursive =
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO RecFlag
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> RecFlag -> IO RecFlag
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RecFlag
Recursive
Word8
_ -> RecFlag -> IO RecFlag
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RecFlag
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
$c== :: Origin -> Origin -> Bool
== :: Origin -> Origin -> Bool
$c/= :: Origin -> Origin -> Bool
/= :: Origin -> Origin -> Bool
Eq, Typeable Origin
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 -> Constr
Origin -> DataType
(forall b. Data b => b -> b) -> Origin -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Origin -> c Origin
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Origin
$ctoConstr :: Origin -> Constr
toConstr :: Origin -> Constr
$cdataTypeOf :: Origin -> DataType
dataTypeOf :: Origin -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Origin)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Origin)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin)
$cgmapT :: (forall b. Data b => b -> b) -> Origin -> Origin
gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Origin -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Origin -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Origin -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Origin -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Origin -> m Origin
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Origin -> m 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
forall doc. IsLine doc => String -> doc
text String
"FromSource"
ppr Origin
Generated = String -> SDoc
forall doc. IsLine doc => String -> doc
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
$c== :: OverlapFlag -> OverlapFlag -> Bool
== :: OverlapFlag -> OverlapFlag -> Bool
$c/= :: OverlapFlag -> OverlapFlag -> Bool
/= :: OverlapFlag -> OverlapFlag -> Bool
Eq, Typeable OverlapFlag
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 -> Constr
OverlapFlag -> DataType
(forall b. Data b => b -> b) -> OverlapFlag -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapFlag
$ctoConstr :: OverlapFlag -> Constr
toConstr :: OverlapFlag -> Constr
$cdataTypeOf :: OverlapFlag -> DataType
dataTypeOf :: OverlapFlag -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapFlag)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapFlag)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapFlag)
$cgmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag
gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OverlapFlag -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OverlapFlag -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapFlag -> m 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 = 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
$c== :: OverlapMode -> OverlapMode -> Bool
== :: OverlapMode -> OverlapMode -> Bool
$c/= :: OverlapMode -> OverlapMode -> Bool
/= :: OverlapMode -> OverlapMode -> Bool
Eq, Typeable OverlapMode
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 -> Constr
OverlapMode -> DataType
(forall b. Data b => b -> b) -> OverlapMode -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OverlapMode -> c OverlapMode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OverlapMode
$ctoConstr :: OverlapMode -> Constr
toConstr :: OverlapMode -> Constr
$cdataTypeOf :: OverlapMode -> DataType
dataTypeOf :: OverlapMode -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapMode)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OverlapMode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapMode)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OverlapMode)
$cgmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode
gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OverlapMode -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OverlapMode -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OverlapMode -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OverlapMode -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OverlapMode -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OverlapMode -> m 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
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
pprSafeOverlap (OverlapFlag -> Bool
isSafeOverlap OverlapFlag
flag)
instance Outputable OverlapMode where
ppr :: OverlapMode -> SDoc
ppr (NoOverlap SourceText
_) = SDoc
forall doc. IsOutput doc => doc
empty
ppr (Overlappable SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[overlappable]"
ppr (Overlapping SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[overlapping]"
ppr (Overlaps SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[overlap ok]"
ppr (Incoherent SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[incoherent]"
instance Binary OverlapMode where
put_ :: BinHandle -> OverlapMode -> IO ()
put_ BinHandle
bh (NoOverlap SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (Overlaps SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (Incoherent SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (Overlapping SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (Overlappable SourceText
s) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4 IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
get :: BinHandle -> IO OverlapMode
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
NoOverlap SourceText
s
Word8
1 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Overlaps SourceText
s
Word8
2 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Incoherent SourceText
s
Word8
3 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Overlapping SourceText
s
Word8
4 -> (BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh) IO SourceText -> (SourceText -> IO OverlapMode) -> IO OverlapMode
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourceText
s -> OverlapMode -> IO OverlapMode
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (OverlapMode -> IO OverlapMode) -> OverlapMode -> IO OverlapMode
forall a b. (a -> b) -> a -> b
$ SourceText -> OverlapMode
Overlappable SourceText
s
Word8
_ -> String -> IO OverlapMode
forall a. HasCallStack => String -> a
panic (String
"get OverlapMode" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
h)
instance Binary OverlapFlag where
put_ :: BinHandle -> OverlapFlag -> IO ()
put_ BinHandle
bh OverlapFlag
flag = do BinHandle -> OverlapMode -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (OverlapFlag -> OverlapMode
overlapMode OverlapFlag
flag)
BinHandle -> Bool -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh (OverlapFlag -> Bool
isSafeOverlap OverlapFlag
flag)
get :: BinHandle -> IO OverlapFlag
get BinHandle
bh = do
OverlapMode
h <- BinHandle -> IO OverlapMode
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Bool
b <- BinHandle -> IO Bool
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
OverlapFlag -> IO OverlapFlag
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OverlapFlag { overlapMode :: OverlapMode
overlapMode = OverlapMode
h, isSafeOverlap :: Bool
isSafeOverlap = Bool
b }
pprSafeOverlap :: Bool -> SDoc
pprSafeOverlap :: Bool -> SDoc
pprSafeOverlap Bool
True = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[safe]"
pprSafeOverlap Bool
False = SDoc
forall doc. IsOutput doc => doc
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
$c== :: PprPrec -> PprPrec -> Bool
== :: PprPrec -> PprPrec -> Bool
$c/= :: PprPrec -> PprPrec -> Bool
/= :: 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
$ccompare :: PprPrec -> PprPrec -> Ordering
compare :: PprPrec -> PprPrec -> Ordering
$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
>= :: PprPrec -> PprPrec -> Bool
$cmax :: PprPrec -> PprPrec -> PprPrec
max :: PprPrec -> PprPrec -> PprPrec
$cmin :: PprPrec -> PprPrec -> PprPrec
min :: PprPrec -> PprPrec -> PprPrec
Ord, Int -> PprPrec -> String -> String
[PprPrec] -> String -> String
PprPrec -> String
(Int -> PprPrec -> String -> String)
-> (PprPrec -> String)
-> ([PprPrec] -> String -> String)
-> Show PprPrec
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PprPrec -> String -> String
showsPrec :: Int -> PprPrec -> String -> String
$cshow :: PprPrec -> String
show :: PprPrec -> String
$cshowList :: [PprPrec] -> String -> String
showList :: [PprPrec] -> String -> String
Show)
topPrec, sigPrec, funPrec, opPrec, starPrec, appPrec, maxPrec :: 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
starPrec :: PprPrec
starPrec = Int -> PprPrec
PprPrec Int
3
appPrec :: PprPrec
appPrec = Int -> PprPrec
PprPrec Int
4
maxPrec :: PprPrec
maxPrec = PprPrec
appPrec
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
forall doc. IsLine doc => doc -> doc
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
$c== :: TupleSort -> TupleSort -> Bool
== :: TupleSort -> TupleSort -> Bool
$c/= :: TupleSort -> TupleSort -> Bool
/= :: TupleSort -> TupleSort -> Bool
Eq, Typeable TupleSort
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 -> Constr
TupleSort -> DataType
(forall b. Data b => b -> b) -> TupleSort -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TupleSort -> c TupleSort
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TupleSort
$ctoConstr :: TupleSort -> Constr
toConstr :: TupleSort -> Constr
$cdataTypeOf :: TupleSort -> DataType
dataTypeOf :: TupleSort -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TupleSort)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TupleSort)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort)
$cgmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort
gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TupleSort -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TupleSort -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TupleSort -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TupleSort -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TupleSort -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TupleSort -> m TupleSort
Data )
instance Outputable TupleSort where
ppr :: TupleSort -> SDoc
ppr TupleSort
ts = String -> SDoc
forall doc. IsLine doc => String -> doc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$
case TupleSort
ts of
TupleSort
BoxedTuple -> String
"BoxedTuple"
TupleSort
UnboxedTuple -> String
"UnboxedTuple"
TupleSort
ConstraintTuple -> String
"ConstraintTuple"
instance Binary TupleSort where
put_ :: BinHandle -> TupleSort -> IO ()
put_ BinHandle
bh TupleSort
BoxedTuple = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh TupleSort
UnboxedTuple = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh TupleSort
ConstraintTuple = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
get :: BinHandle -> IO TupleSort
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> TupleSort -> IO TupleSort
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TupleSort
BoxedTuple
Word8
1 -> TupleSort -> IO TupleSort
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TupleSort
UnboxedTuple
Word8
_ -> TupleSort -> IO TupleSort
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TupleSort
ConstraintTuple
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
forall doc. IsLine doc => doc -> doc
parens SDoc
p
tupleParens TupleSort
UnboxedTuple SDoc
p = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(#" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
p SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"#)"
tupleParens TupleSort
ConstraintTuple SDoc
p
= SDoc -> SDoc -> SDoc
forall doc. IsOutput doc => doc -> doc -> doc
ifPprDebug (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(%" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
p SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"%)")
(SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens SDoc
p)
sumParens :: SDoc -> SDoc
sumParens :: SDoc -> SDoc
sumParens SDoc
p = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"(#" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
p SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"#)"
pprAlternative :: (a -> SDoc)
-> a
-> ConTag
-> Arity
-> SDoc
pprAlternative :: forall a. (a -> SDoc) -> a -> Int -> Int -> SDoc
pprAlternative a -> SDoc
pp a
x Int
alt Int
arity =
[SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
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
forall doc. IsLine doc => doc
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
forall doc. IsLine doc => doc
vbar)
data UnboxedTupleOrSum
= UnboxedTupleType
| UnboxedSumType
deriving UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool
(UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool)
-> (UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool)
-> Eq UnboxedTupleOrSum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool
== :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool
$c/= :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool
/= :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool
Eq
instance Outputable UnboxedTupleOrSum where
ppr :: UnboxedTupleOrSum -> SDoc
ppr UnboxedTupleOrSum
UnboxedTupleType = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"UnboxedTupleType"
ppr UnboxedTupleOrSum
UnboxedSumType = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"UnboxedSumType"
unboxedTupleOrSumExtension :: UnboxedTupleOrSum -> LangExt.Extension
unboxedTupleOrSumExtension :: UnboxedTupleOrSum -> Extension
unboxedTupleOrSumExtension UnboxedTupleOrSum
UnboxedTupleType = Extension
LangExt.UnboxedTuples
unboxedTupleOrSumExtension UnboxedTupleOrSum
UnboxedSumType = Extension
LangExt.UnboxedSums
data EP a = EP { forall a. EP a -> a
fromEP :: a,
forall a. EP a -> a
toEP :: a }
data OccInfo
= ManyOccs { OccInfo -> TailCallInfo
occ_tail :: !TailCallInfo }
| IAmDead
| OneOcc { OccInfo -> InsideLam
occ_in_lam :: !InsideLam
, OccInfo -> Int
occ_n_br :: {-# UNPACK #-} !BranchCount
, OccInfo -> InterestingCxt
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
$c== :: OccInfo -> OccInfo -> Bool
== :: OccInfo -> OccInfo -> Bool
$c/= :: OccInfo -> OccInfo -> Bool
/= :: OccInfo -> OccInfo -> Bool
Eq)
type RulesOnly = Bool
type BranchCount = Int
oneBranch :: BranchCount
oneBranch :: Int
oneBranch = Int
1
noOccInfo :: OccInfo
noOccInfo :: OccInfo
noOccInfo = ManyOccs { occ_tail :: TailCallInfo
occ_tail = TailCallInfo
NoTailCallInfo }
isNoOccInfo :: OccInfo -> Bool
isNoOccInfo :: OccInfo -> Bool
isNoOccInfo ManyOccs { occ_tail :: OccInfo -> TailCallInfo
occ_tail = TailCallInfo
NoTailCallInfo } = Bool
True
isNoOccInfo OccInfo
_ = Bool
False
isManyOccs :: OccInfo -> Bool
isManyOccs :: OccInfo -> Bool
isManyOccs ManyOccs{} = Bool
True
isManyOccs OccInfo
_ = Bool
False
seqOccInfo :: OccInfo -> ()
seqOccInfo :: OccInfo -> ()
seqOccInfo OccInfo
occ = OccInfo
occ OccInfo -> () -> ()
forall a b. a -> b -> b
`seq` ()
data InterestingCxt
= IsInteresting
| NotInteresting
deriving (InterestingCxt -> InterestingCxt -> Bool
(InterestingCxt -> InterestingCxt -> Bool)
-> (InterestingCxt -> InterestingCxt -> Bool) -> Eq InterestingCxt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterestingCxt -> InterestingCxt -> Bool
== :: InterestingCxt -> InterestingCxt -> Bool
$c/= :: InterestingCxt -> InterestingCxt -> Bool
/= :: InterestingCxt -> InterestingCxt -> Bool
Eq)
instance Semi.Semigroup InterestingCxt where
InterestingCxt
NotInteresting <> :: InterestingCxt -> InterestingCxt -> InterestingCxt
<> InterestingCxt
x = InterestingCxt
x
InterestingCxt
IsInteresting <> InterestingCxt
_ = InterestingCxt
IsInteresting
instance Monoid InterestingCxt where
mempty :: InterestingCxt
mempty = InterestingCxt
NotInteresting
mappend :: InterestingCxt -> InterestingCxt -> InterestingCxt
mappend = InterestingCxt -> InterestingCxt -> InterestingCxt
forall a. Semigroup a => a -> a -> a
(Semi.<>)
data InsideLam
= IsInsideLam
| NotInsideLam
deriving (InsideLam -> InsideLam -> Bool
(InsideLam -> InsideLam -> Bool)
-> (InsideLam -> InsideLam -> Bool) -> Eq InsideLam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsideLam -> InsideLam -> Bool
== :: InsideLam -> InsideLam -> Bool
$c/= :: InsideLam -> InsideLam -> Bool
/= :: InsideLam -> InsideLam -> Bool
Eq)
instance Semi.Semigroup InsideLam where
InsideLam
NotInsideLam <> :: InsideLam -> InsideLam -> InsideLam
<> InsideLam
x = InsideLam
x
InsideLam
IsInsideLam <> InsideLam
_ = InsideLam
IsInsideLam
instance Monoid InsideLam where
mempty :: InsideLam
mempty = InsideLam
NotInsideLam
mappend :: InsideLam -> InsideLam -> InsideLam
mappend = InsideLam -> InsideLam -> InsideLam
forall a. Semigroup a => a -> a -> a
(Semi.<>)
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
$c== :: TailCallInfo -> TailCallInfo -> Bool
== :: TailCallInfo -> TailCallInfo -> Bool
$c/= :: TailCallInfo -> TailCallInfo -> Bool
/= :: 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 = 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
forall doc. IsLine doc => [doc] -> doc
sep [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Tail", Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
ar ]
ppr TailCallInfo
_ = SDoc
forall doc. IsOutput doc => doc
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
forall doc. IsLine doc => String -> doc
text String
"Dead"
ppr (IAmALoopBreaker Bool
rule_only TailCallInfo
tails)
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LoopBreaker" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
pp_ro SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> TailCallInfo -> SDoc
pprShortTailCallInfo TailCallInfo
tails
where
pp_ro :: SDoc
pp_ro | Bool
rule_only = Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'!'
| Bool
otherwise = SDoc
forall doc. IsOutput doc => doc
empty
ppr (OneOcc InsideLam
inside_lam Int
one_branch InterestingCxt
int_cxt TailCallInfo
tail_info)
= String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Once" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> InsideLam -> SDoc
forall {doc}. IsLine doc => InsideLam -> doc
pp_lam InsideLam
inside_lam SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int
one_branch SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> InterestingCxt -> SDoc
forall {doc}. IsLine doc => InterestingCxt -> doc
pp_args InterestingCxt
int_cxt SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
pp_tail
where
pp_lam :: InsideLam -> doc
pp_lam InsideLam
IsInsideLam = Char -> doc
forall doc. IsLine doc => Char -> doc
char Char
'L'
pp_lam InsideLam
NotInsideLam = doc
forall doc. IsOutput doc => doc
empty
pp_args :: InterestingCxt -> doc
pp_args InterestingCxt
IsInteresting = Char -> doc
forall doc. IsLine doc => Char -> doc
char Char
'!'
pp_args InterestingCxt
NotInteresting = doc
forall doc. IsOutput doc => doc
empty
pp_tail :: SDoc
pp_tail = TailCallInfo -> SDoc
pprShortTailCallInfo TailCallInfo
tail_info
pprShortTailCallInfo :: TailCallInfo -> SDoc
pprShortTailCallInfo :: TailCallInfo -> SDoc
pprShortTailCallInfo (AlwaysTailCalled Int
ar) = Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'T' SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
ar)
pprShortTailCallInfo TailCallInfo
NoTailCallInfo = SDoc
forall doc. IsOutput doc => doc
empty
data DefMethSpec ty
= VanillaDM
| GenericDM ty
instance Outputable (DefMethSpec ty) where
ppr :: DefMethSpec ty -> SDoc
ppr DefMethSpec ty
VanillaDM = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"{- Has default method -}"
ppr (GenericDM {}) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"{- Has generic default method -}"
data SuccessFlag = Succeeded | Failed
instance Semigroup SuccessFlag where
SuccessFlag
Failed <> :: SuccessFlag -> SuccessFlag -> SuccessFlag
<> SuccessFlag
_ = SuccessFlag
Failed
SuccessFlag
_ <> SuccessFlag
Failed = SuccessFlag
Failed
SuccessFlag
_ <> SuccessFlag
_ = SuccessFlag
Succeeded
instance Outputable SuccessFlag where
ppr :: SuccessFlag -> SDoc
ppr SuccessFlag
Succeeded = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Succeeded"
ppr SuccessFlag
Failed = String -> SDoc
forall doc. IsLine doc => String -> doc
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
type PhaseNum = Int
data CompilerPhase
= InitialPhase
| Phase PhaseNum
| FinalPhase
deriving CompilerPhase -> CompilerPhase -> Bool
(CompilerPhase -> CompilerPhase -> Bool)
-> (CompilerPhase -> CompilerPhase -> Bool) -> Eq CompilerPhase
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompilerPhase -> CompilerPhase -> Bool
== :: CompilerPhase -> CompilerPhase -> Bool
$c/= :: CompilerPhase -> CompilerPhase -> Bool
/= :: CompilerPhase -> CompilerPhase -> Bool
Eq
instance Outputable CompilerPhase where
ppr :: CompilerPhase -> SDoc
ppr (Phase Int
n) = Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
n
ppr CompilerPhase
InitialPhase = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"InitialPhase"
ppr CompilerPhase
FinalPhase = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"FinalPhase"
data Activation
= AlwaysActive
| ActiveBefore SourceText PhaseNum
| ActiveAfter SourceText PhaseNum
| FinalActive
| NeverActive
deriving( Activation -> Activation -> Bool
(Activation -> Activation -> Bool)
-> (Activation -> Activation -> Bool) -> Eq Activation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Activation -> Activation -> Bool
== :: Activation -> Activation -> Bool
$c/= :: Activation -> Activation -> Bool
/= :: Activation -> Activation -> Bool
Eq, Typeable Activation
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 -> Constr
Activation -> DataType
(forall b. Data b => b -> b) -> Activation -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Activation -> c Activation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Activation
$ctoConstr :: Activation -> Constr
toConstr :: Activation -> Constr
$cdataTypeOf :: Activation -> DataType
dataTypeOf :: Activation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Activation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Activation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation)
$cgmapT :: (forall b. Data b => b -> b) -> Activation -> Activation
gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Activation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Activation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Activation -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Activation -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Activation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Activation -> m Activation
Data )
beginPhase :: Activation -> CompilerPhase
beginPhase :: Activation -> CompilerPhase
beginPhase Activation
AlwaysActive = CompilerPhase
InitialPhase
beginPhase (ActiveBefore {}) = CompilerPhase
InitialPhase
beginPhase (ActiveAfter SourceText
_ Int
n) = Int -> CompilerPhase
Phase Int
n
beginPhase Activation
FinalActive = CompilerPhase
FinalPhase
beginPhase Activation
NeverActive = CompilerPhase
FinalPhase
activeAfter :: CompilerPhase -> Activation
activeAfter :: CompilerPhase -> Activation
activeAfter CompilerPhase
InitialPhase = Activation
AlwaysActive
activeAfter (Phase Int
n) = SourceText -> Int -> Activation
ActiveAfter SourceText
NoSourceText Int
n
activeAfter CompilerPhase
FinalPhase = Activation
FinalActive
nextPhase :: CompilerPhase -> CompilerPhase
nextPhase :: CompilerPhase -> CompilerPhase
nextPhase CompilerPhase
InitialPhase = Int -> CompilerPhase
Phase Int
2
nextPhase (Phase Int
0) = CompilerPhase
FinalPhase
nextPhase (Phase Int
n) = Int -> CompilerPhase
Phase (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
nextPhase CompilerPhase
FinalPhase = CompilerPhase
FinalPhase
laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase
laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase
laterPhase (Phase Int
n1) (Phase Int
n2) = Int -> CompilerPhase
Phase (Int
n1 Int -> Int -> Int
forall a. Ord a => a -> a -> a
`min` Int
n2)
laterPhase CompilerPhase
InitialPhase CompilerPhase
p2 = CompilerPhase
p2
laterPhase CompilerPhase
FinalPhase CompilerPhase
_ = CompilerPhase
FinalPhase
laterPhase CompilerPhase
p1 CompilerPhase
InitialPhase = CompilerPhase
p1
laterPhase CompilerPhase
_ CompilerPhase
FinalPhase = CompilerPhase
FinalPhase
activateAfterInitial :: Activation
activateAfterInitial :: Activation
activateAfterInitial = CompilerPhase -> Activation
activeAfter (CompilerPhase -> CompilerPhase
nextPhase CompilerPhase
InitialPhase)
activateDuringFinal :: Activation
activateDuringFinal :: Activation
activateDuringFinal = Activation
FinalActive
isActive :: CompilerPhase -> Activation -> Bool
isActive :: CompilerPhase -> Activation -> Bool
isActive CompilerPhase
InitialPhase Activation
act = Activation -> Bool
activeInInitialPhase Activation
act
isActive (Phase Int
p) Activation
act = Int -> Activation -> Bool
activeInPhase Int
p Activation
act
isActive CompilerPhase
FinalPhase Activation
act = Activation -> Bool
activeInFinalPhase Activation
act
activeInInitialPhase :: Activation -> Bool
activeInInitialPhase :: Activation -> Bool
activeInInitialPhase Activation
AlwaysActive = Bool
True
activeInInitialPhase (ActiveBefore {}) = Bool
True
activeInInitialPhase Activation
_ = Bool
False
activeInPhase :: PhaseNum -> Activation -> Bool
activeInPhase :: Int -> Activation -> Bool
activeInPhase Int
_ Activation
AlwaysActive = Bool
True
activeInPhase Int
_ Activation
NeverActive = Bool
False
activeInPhase Int
_ Activation
FinalActive = Bool
False
activeInPhase Int
p (ActiveAfter SourceText
_ Int
n) = Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n
activeInPhase Int
p (ActiveBefore SourceText
_ Int
n) = Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n
activeInFinalPhase :: Activation -> Bool
activeInFinalPhase :: Activation -> Bool
activeInFinalPhase Activation
AlwaysActive = Bool
True
activeInFinalPhase Activation
FinalActive = Bool
True
activeInFinalPhase (ActiveAfter {}) = Bool
True
activeInFinalPhase Activation
_ = Bool
False
isNeverActive, isAlwaysActive :: 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
competesWith :: Activation -> Activation -> Bool
competesWith :: Activation -> Activation -> Bool
competesWith Activation
AlwaysActive Activation
_ = Bool
True
competesWith Activation
NeverActive Activation
_ = Bool
False
competesWith Activation
_ Activation
NeverActive = Bool
False
competesWith Activation
FinalActive Activation
FinalActive = Bool
True
competesWith Activation
FinalActive Activation
_ = Bool
False
competesWith (ActiveBefore {}) Activation
AlwaysActive = Bool
True
competesWith (ActiveBefore {}) Activation
FinalActive = Bool
False
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 {}) Activation
FinalActive = Bool
True
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
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
$c== :: InlinePragma -> InlinePragma -> Bool
== :: InlinePragma -> InlinePragma -> Bool
$c/= :: InlinePragma -> InlinePragma -> Bool
/= :: InlinePragma -> InlinePragma -> Bool
Eq, Typeable InlinePragma
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 -> Constr
InlinePragma -> DataType
(forall b. Data b => b -> b) -> InlinePragma -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlinePragma -> c InlinePragma
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlinePragma
$ctoConstr :: InlinePragma -> Constr
toConstr :: InlinePragma -> Constr
$cdataTypeOf :: InlinePragma -> DataType
dataTypeOf :: InlinePragma -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlinePragma)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlinePragma)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlinePragma)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c InlinePragma)
$cgmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma
gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlinePragma -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> InlinePragma -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> InlinePragma -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InlinePragma -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InlinePragma -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma
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
$c== :: RuleMatchInfo -> RuleMatchInfo -> Bool
== :: RuleMatchInfo -> RuleMatchInfo -> Bool
$c/= :: RuleMatchInfo -> RuleMatchInfo -> Bool
/= :: RuleMatchInfo -> RuleMatchInfo -> Bool
Eq, Typeable RuleMatchInfo
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 -> Constr
RuleMatchInfo -> DataType
(forall b. Data b => b -> b) -> RuleMatchInfo -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RuleMatchInfo
$ctoConstr :: RuleMatchInfo -> Constr
toConstr :: RuleMatchInfo -> Constr
$cdataTypeOf :: RuleMatchInfo -> DataType
dataTypeOf :: RuleMatchInfo -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RuleMatchInfo)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RuleMatchInfo)
$cgmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo
gmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RuleMatchInfo -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RuleMatchInfo -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo
Data, Int -> RuleMatchInfo -> String -> String
[RuleMatchInfo] -> String -> String
RuleMatchInfo -> String
(Int -> RuleMatchInfo -> String -> String)
-> (RuleMatchInfo -> String)
-> ([RuleMatchInfo] -> String -> String)
-> Show RuleMatchInfo
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RuleMatchInfo -> String -> String
showsPrec :: Int -> RuleMatchInfo -> String -> String
$cshow :: RuleMatchInfo -> String
show :: RuleMatchInfo -> String
$cshowList :: [RuleMatchInfo] -> String -> String
showList :: [RuleMatchInfo] -> String -> String
Show )
data InlineSpec
= Inline SourceText
| Inlinable SourceText
| NoInline SourceText
| Opaque SourceText
| NoUserInlinePrag
deriving( InlineSpec -> InlineSpec -> Bool
(InlineSpec -> InlineSpec -> Bool)
-> (InlineSpec -> InlineSpec -> Bool) -> Eq InlineSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InlineSpec -> InlineSpec -> Bool
== :: InlineSpec -> InlineSpec -> Bool
$c/= :: InlineSpec -> InlineSpec -> Bool
/= :: InlineSpec -> InlineSpec -> Bool
Eq, Typeable InlineSpec
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 -> Constr
InlineSpec -> DataType
(forall b. Data b => b -> b) -> InlineSpec -> 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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> InlineSpec -> c InlineSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c InlineSpec
$ctoConstr :: InlineSpec -> Constr
toConstr :: InlineSpec -> Constr
$cdataTypeOf :: InlineSpec -> DataType
dataTypeOf :: InlineSpec -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlineSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c InlineSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec)
$cgmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec
gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
gmapQl :: forall r r'.
(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
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> InlineSpec -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> InlineSpec -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> InlineSpec -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InlineSpec -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> InlineSpec -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(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
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(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
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec
Data, Int -> InlineSpec -> String -> String
[InlineSpec] -> String -> String
InlineSpec -> String
(Int -> InlineSpec -> String -> String)
-> (InlineSpec -> String)
-> ([InlineSpec] -> String -> String)
-> Show InlineSpec
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InlineSpec -> String -> String
showsPrec :: Int -> InlineSpec -> String -> String
$cshow :: InlineSpec -> String
show :: InlineSpec -> String
$cshowList :: [InlineSpec] -> String -> String
showList :: [InlineSpec] -> String -> String
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
NoUserInlinePrag = Bool
True
noUserInlineSpec InlineSpec
_ = Bool
False
defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma
:: InlinePragma
defaultInlinePragma :: InlinePragma
defaultInlinePragma = 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
NoUserInlinePrag
, inl_sat :: Maybe Int
inl_sat = Maybe Int
forall a. Maybe a
Nothing }
alwaysInlinePragma :: InlinePragma
alwaysInlinePragma = InlinePragma
defaultInlinePragma { inl_inline = Inline (inlinePragmaSource defaultInlinePragma) }
neverInlinePragma :: InlinePragma
neverInlinePragma = InlinePragma
defaultInlinePragma { inl_act = NeverActive }
alwaysInlineConLikePragma :: InlinePragma
alwaysInlineConLikePragma :: InlinePragma
alwaysInlineConLikePragma = InlinePragma
alwaysInlinePragma { inl_rule = ConLike }
inlinePragmaSpec :: InlinePragma -> InlineSpec
inlinePragmaSpec :: InlinePragma -> InlineSpec
inlinePragmaSpec = InlinePragma -> InlineSpec
inl_inline
inlinePragmaSource :: InlinePragma -> SourceText
inlinePragmaSource :: InlinePragma -> SourceText
inlinePragmaSource InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
Inline SourceText
x -> SourceText
x
Inlinable SourceText
y -> SourceText
y
NoInline SourceText
z -> SourceText
z
Opaque SourceText
q -> SourceText
q
InlineSpec
NoUserInlinePrag -> SourceText
NoSourceText
inlineSpecSource :: InlineSpec -> SourceText
inlineSpecSource :: InlineSpec -> SourceText
inlineSpecSource InlineSpec
spec = case InlineSpec
spec of
Inline SourceText
x -> SourceText
x
Inlinable SourceText
y -> SourceText
y
NoInline SourceText
z -> SourceText
z
Opaque SourceText
q -> SourceText
q
InlineSpec
NoUserInlinePrag -> SourceText
NoSourceText
dfunInlinePragma :: InlinePragma
dfunInlinePragma = InlinePragma
defaultInlinePragma { inl_act = AlwaysActive
, inl_rule = 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
Inline SourceText
_ -> Bool
True
InlineSpec
_ -> Bool
False
isInlinablePragma :: InlinePragma -> Bool
isInlinablePragma :: InlinePragma -> Bool
isInlinablePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
Inlinable SourceText
_ -> Bool
True
InlineSpec
_ -> Bool
False
isNoInlinePragma :: InlinePragma -> Bool
isNoInlinePragma :: InlinePragma -> Bool
isNoInlinePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
NoInline SourceText
_ -> Bool
True
InlineSpec
_ -> Bool
False
isAnyInlinePragma :: InlinePragma -> Bool
isAnyInlinePragma :: InlinePragma -> Bool
isAnyInlinePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
Inline SourceText
_ -> Bool
True
Inlinable SourceText
_ -> Bool
True
InlineSpec
_ -> Bool
False
isOpaquePragma :: InlinePragma -> Bool
isOpaquePragma :: InlinePragma -> Bool
isOpaquePragma InlinePragma
prag = case InlinePragma -> InlineSpec
inl_inline InlinePragma
prag of
Opaque SourceText
_ -> 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 }
setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
setInlinePragmaRuleMatchInfo InlinePragma
prag RuleMatchInfo
info = InlinePragma
prag { inl_rule = info }
instance Outputable Activation where
ppr :: Activation -> SDoc
ppr Activation
AlwaysActive = SDoc
forall doc. IsOutput doc => doc
empty
ppr Activation
NeverActive = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"~")
ppr (ActiveBefore SourceText
_ Int
n) = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (Char -> SDoc
forall doc. IsLine doc => Char -> doc
char Char
'~' SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
n)
ppr (ActiveAfter SourceText
_ Int
n) = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
n)
ppr Activation
FinalActive = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"[final]"
instance Binary Activation where
put_ :: BinHandle -> Activation -> IO ()
put_ BinHandle
bh Activation
NeverActive =
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh Activation
FinalActive =
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh Activation
AlwaysActive =
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
put_ BinHandle
bh (ActiveBefore SourceText
src Int
aa) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
src
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
aa
put_ BinHandle
bh (ActiveAfter SourceText
src Int
ab) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
src
BinHandle -> Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Int
ab
get :: BinHandle -> IO Activation
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> Activation -> IO Activation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Activation
NeverActive
Word8
1 -> Activation -> IO Activation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Activation
FinalActive
Word8
2 -> Activation -> IO Activation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Activation
AlwaysActive
Word8
3 -> do SourceText
src <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Int
aa <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Activation -> IO Activation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> Int -> Activation
ActiveBefore SourceText
src Int
aa)
Word8
_ -> do SourceText
src <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Int
ab <- BinHandle -> IO Int
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Activation -> IO Activation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> Int -> Activation
ActiveAfter SourceText
src Int
ab)
instance Outputable RuleMatchInfo where
ppr :: RuleMatchInfo -> SDoc
ppr RuleMatchInfo
ConLike = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"CONLIKE"
ppr RuleMatchInfo
FunLike = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"FUNLIKE"
instance Binary RuleMatchInfo where
put_ :: BinHandle -> RuleMatchInfo -> IO ()
put_ BinHandle
bh RuleMatchInfo
FunLike = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh RuleMatchInfo
ConLike = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
get :: BinHandle -> IO RuleMatchInfo
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
if Word8
h Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
1 then RuleMatchInfo -> IO RuleMatchInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RuleMatchInfo
ConLike
else RuleMatchInfo -> IO RuleMatchInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return RuleMatchInfo
FunLike
instance Outputable InlineSpec where
ppr :: InlineSpec -> SDoc
ppr (Inline SourceText
src) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"INLINE" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
src SDoc
forall doc. IsOutput doc => doc
empty
ppr (NoInline SourceText
src) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NOINLINE" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
src SDoc
forall doc. IsOutput doc => doc
empty
ppr (Inlinable SourceText
src) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"INLINABLE" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
src SDoc
forall doc. IsOutput doc => doc
empty
ppr (Opaque SourceText
src) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"OPAQUE" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SourceText -> SDoc -> SDoc
pprWithSourceText SourceText
src SDoc
forall doc. IsOutput doc => doc
empty
ppr InlineSpec
NoUserInlinePrag = SDoc
forall doc. IsOutput doc => doc
empty
instance Binary InlineSpec where
put_ :: BinHandle -> InlineSpec -> IO ()
put_ BinHandle
bh InlineSpec
NoUserInlinePrag = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh (Inline SourceText
s) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (Inlinable SourceText
s) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (NoInline SourceText
s) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
put_ BinHandle
bh (Opaque SourceText
s) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
get :: BinHandle -> IO InlineSpec
get BinHandle
bh = do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> InlineSpec -> IO InlineSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return InlineSpec
NoUserInlinePrag
Word8
1 -> do
SourceText
s <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
InlineSpec -> IO InlineSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> InlineSpec
Inline SourceText
s)
Word8
2 -> do
SourceText
s <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
InlineSpec -> IO InlineSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> InlineSpec
Inlinable SourceText
s)
Word8
3 -> do
SourceText
s <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
InlineSpec -> IO InlineSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> InlineSpec
NoInline SourceText
s)
Word8
_ -> do
SourceText
s <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
InlineSpec -> IO InlineSpec
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText -> InlineSpec
Opaque SourceText
s)
instance Outputable InlinePragma where
ppr :: InlinePragma -> SDoc
ppr = InlinePragma -> SDoc
pprInline
instance Binary InlinePragma where
put_ :: BinHandle -> InlinePragma -> IO ()
put_ BinHandle
bh (InlinePragma SourceText
s InlineSpec
a Maybe Int
b Activation
c RuleMatchInfo
d) = do
BinHandle -> SourceText -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh SourceText
s
BinHandle -> InlineSpec -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh InlineSpec
a
BinHandle -> Maybe Int -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Int
b
BinHandle -> Activation -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Activation
c
BinHandle -> RuleMatchInfo -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh RuleMatchInfo
d
get :: BinHandle -> IO InlinePragma
get BinHandle
bh = do
SourceText
s <- BinHandle -> IO SourceText
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
InlineSpec
a <- BinHandle -> IO InlineSpec
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Maybe Int
b <- BinHandle -> IO (Maybe Int)
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Activation
c <- BinHandle -> IO Activation
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
RuleMatchInfo
d <- BinHandle -> IO RuleMatchInfo
forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
InlinePragma -> IO InlinePragma
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceText
-> InlineSpec
-> Maybe Int
-> Activation
-> RuleMatchInfo
-> InlinePragma
InlinePragma SourceText
s InlineSpec
a Maybe Int
b Activation
c RuleMatchInfo
d)
inlinePragmaName :: InlineSpec -> SDoc
inlinePragmaName :: InlineSpec -> SDoc
inlinePragmaName (Inline SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"INLINE"
inlinePragmaName (Inlinable SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"INLINABLE"
inlinePragmaName (NoInline SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NOINLINE"
inlinePragmaName (Opaque SourceText
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"OPAQUE"
inlinePragmaName InlineSpec
NoUserInlinePrag = SDoc
forall doc. IsOutput doc => doc
empty
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
pp_inl InlineSpec
inline SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> InlineSpec -> Activation -> SDoc
pp_act InlineSpec
inline Activation
activation SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_sat SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
pp_info
where
pp_inl :: InlineSpec -> SDoc
pp_inl InlineSpec
x = if Bool
emptyInline then SDoc
forall doc. IsOutput doc => doc
empty else InlineSpec -> SDoc
inlinePragmaName InlineSpec
x
pp_act :: InlineSpec -> Activation -> SDoc
pp_act Inline {} Activation
AlwaysActive = SDoc
forall doc. IsOutput doc => doc
empty
pp_act NoInline {} Activation
NeverActive = SDoc
forall doc. IsOutput doc => doc
empty
pp_act Opaque {} Activation
NeverActive = SDoc
forall doc. IsOutput doc => doc
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
forall doc. IsLine doc => doc -> doc
parens (String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"sat-args=" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
ar)
| Bool
otherwise = SDoc
forall doc. IsOutput doc => doc
empty
pp_info :: SDoc
pp_info | RuleMatchInfo -> Bool
isFunLike RuleMatchInfo
info = SDoc
forall doc. IsOutput doc => doc
empty
| Bool
otherwise = RuleMatchInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr RuleMatchInfo
info
data UnfoldingSource
=
VanillaSrc
| StableUserSrc
| StableSystemSrc
| CompulsorySrc
isStableUserSource :: UnfoldingSource -> Bool
isStableUserSource :: UnfoldingSource -> Bool
isStableUserSource UnfoldingSource
StableUserSrc = Bool
True
isStableUserSource UnfoldingSource
_ = Bool
False
isStableSystemSource :: UnfoldingSource -> Bool
isStableSystemSource :: UnfoldingSource -> Bool
isStableSystemSource UnfoldingSource
StableSystemSrc = Bool
True
isStableSystemSource UnfoldingSource
_ = Bool
False
isCompulsorySource :: UnfoldingSource -> Bool
isCompulsorySource :: UnfoldingSource -> Bool
isCompulsorySource UnfoldingSource
CompulsorySrc = Bool
True
isCompulsorySource UnfoldingSource
_ = Bool
False
isStableSource :: UnfoldingSource -> Bool
isStableSource :: UnfoldingSource -> Bool
isStableSource UnfoldingSource
CompulsorySrc = Bool
True
isStableSource UnfoldingSource
StableSystemSrc = Bool
True
isStableSource UnfoldingSource
StableUserSrc = Bool
True
isStableSource UnfoldingSource
VanillaSrc = Bool
False
instance Binary UnfoldingSource where
put_ :: BinHandle -> UnfoldingSource -> IO ()
put_ BinHandle
bh UnfoldingSource
CompulsorySrc = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0
put_ BinHandle
bh UnfoldingSource
StableUserSrc = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1
put_ BinHandle
bh UnfoldingSource
StableSystemSrc = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
put_ BinHandle
bh UnfoldingSource
VanillaSrc = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
get :: BinHandle -> IO UnfoldingSource
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> UnfoldingSource -> IO UnfoldingSource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UnfoldingSource
CompulsorySrc
Word8
1 -> UnfoldingSource -> IO UnfoldingSource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UnfoldingSource
StableUserSrc
Word8
2 -> UnfoldingSource -> IO UnfoldingSource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UnfoldingSource
StableSystemSrc
Word8
_ -> UnfoldingSource -> IO UnfoldingSource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return UnfoldingSource
VanillaSrc
instance Outputable UnfoldingSource where
ppr :: UnfoldingSource -> SDoc
ppr UnfoldingSource
CompulsorySrc = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Compulsory"
ppr UnfoldingSource
StableUserSrc = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"StableUser"
ppr UnfoldingSource
StableSystemSrc = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"StableSystem"
ppr UnfoldingSource
VanillaSrc = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"<vanilla>"
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
$c== :: IntWithInf -> IntWithInf -> Bool
== :: IntWithInf -> IntWithInf -> Bool
$c/= :: IntWithInf -> IntWithInf -> Bool
/= :: 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
forall doc. IsLine doc => Char -> doc
char Char
'∞'
ppr (Int Int
n) = Int -> SDoc
forall doc. IsLine doc => Int -> doc
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. HasCallStack => 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)
subWithInf :: IntWithInf -> Int -> IntWithInf
subWithInf :: IntWithInf -> Int -> IntWithInf
subWithInf IntWithInf
Infinity Int
_ = IntWithInf
Infinity
subWithInf (Int Int
a) 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 TypeOrKind = TypeLevel | KindLevel
deriving TypeOrKind -> TypeOrKind -> Bool
(TypeOrKind -> TypeOrKind -> Bool)
-> (TypeOrKind -> TypeOrKind -> Bool) -> Eq TypeOrKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeOrKind -> TypeOrKind -> Bool
== :: TypeOrKind -> TypeOrKind -> Bool
$c/= :: TypeOrKind -> TypeOrKind -> Bool
/= :: TypeOrKind -> TypeOrKind -> Bool
Eq
instance Outputable TypeOrKind where
ppr :: TypeOrKind -> SDoc
ppr TypeOrKind
TypeLevel = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"TypeLevel"
ppr TypeOrKind
KindLevel = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"KindLevel"
isTypeLevel :: TypeOrKind -> Bool
isTypeLevel :: TypeOrKind -> Bool
isTypeLevel TypeOrKind
TypeLevel = Bool
True
isTypeLevel TypeOrKind
KindLevel = Bool
False
isKindLevel :: TypeOrKind -> Bool
isKindLevel :: TypeOrKind -> Bool
isKindLevel TypeOrKind
TypeLevel = Bool
False
isKindLevel TypeOrKind
KindLevel = Bool
True
data Levity
= Lifted
| Unlifted
deriving Levity -> Levity -> Bool
(Levity -> Levity -> Bool)
-> (Levity -> Levity -> Bool) -> Eq Levity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Levity -> Levity -> Bool
== :: Levity -> Levity -> Bool
$c/= :: Levity -> Levity -> Bool
/= :: Levity -> Levity -> Bool
Eq
instance Outputable Levity where
ppr :: Levity -> SDoc
ppr Levity
Lifted = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Lifted"
ppr Levity
Unlifted = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Unlifted"
mightBeLifted :: Maybe Levity -> Bool
mightBeLifted :: Maybe Levity -> Bool
mightBeLifted (Just Levity
Unlifted) = Bool
False
mightBeLifted Maybe Levity
_ = Bool
True
mightBeUnlifted :: Maybe Levity -> Bool
mightBeUnlifted :: Maybe Levity -> Bool
mightBeUnlifted (Just Levity
Lifted) = Bool
False
mightBeUnlifted Maybe Levity
_ = Bool
True
data TypeOrConstraint
= TypeLike | ConstraintLike
deriving( TypeOrConstraint -> TypeOrConstraint -> Bool
(TypeOrConstraint -> TypeOrConstraint -> Bool)
-> (TypeOrConstraint -> TypeOrConstraint -> Bool)
-> Eq TypeOrConstraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeOrConstraint -> TypeOrConstraint -> Bool
== :: TypeOrConstraint -> TypeOrConstraint -> Bool
$c/= :: TypeOrConstraint -> TypeOrConstraint -> Bool
/= :: TypeOrConstraint -> TypeOrConstraint -> Bool
Eq, Eq TypeOrConstraint
Eq TypeOrConstraint =>
(TypeOrConstraint -> TypeOrConstraint -> Ordering)
-> (TypeOrConstraint -> TypeOrConstraint -> Bool)
-> (TypeOrConstraint -> TypeOrConstraint -> Bool)
-> (TypeOrConstraint -> TypeOrConstraint -> Bool)
-> (TypeOrConstraint -> TypeOrConstraint -> Bool)
-> (TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint)
-> (TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint)
-> Ord TypeOrConstraint
TypeOrConstraint -> TypeOrConstraint -> Bool
TypeOrConstraint -> TypeOrConstraint -> Ordering
TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint
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
$ccompare :: TypeOrConstraint -> TypeOrConstraint -> Ordering
compare :: TypeOrConstraint -> TypeOrConstraint -> Ordering
$c< :: TypeOrConstraint -> TypeOrConstraint -> Bool
< :: TypeOrConstraint -> TypeOrConstraint -> Bool
$c<= :: TypeOrConstraint -> TypeOrConstraint -> Bool
<= :: TypeOrConstraint -> TypeOrConstraint -> Bool
$c> :: TypeOrConstraint -> TypeOrConstraint -> Bool
> :: TypeOrConstraint -> TypeOrConstraint -> Bool
$c>= :: TypeOrConstraint -> TypeOrConstraint -> Bool
>= :: TypeOrConstraint -> TypeOrConstraint -> Bool
$cmax :: TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint
max :: TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint
$cmin :: TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint
min :: TypeOrConstraint -> TypeOrConstraint -> TypeOrConstraint
Ord, Typeable TypeOrConstraint
Typeable TypeOrConstraint =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeOrConstraint -> c TypeOrConstraint)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeOrConstraint)
-> (TypeOrConstraint -> Constr)
-> (TypeOrConstraint -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeOrConstraint))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TypeOrConstraint))
-> ((forall b. Data b => b -> b)
-> TypeOrConstraint -> TypeOrConstraint)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r)
-> (forall u.
(forall d. Data d => d -> u) -> TypeOrConstraint -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TypeOrConstraint -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint)
-> Data TypeOrConstraint
TypeOrConstraint -> Constr
TypeOrConstraint -> DataType
(forall b. Data b => b -> b)
-> TypeOrConstraint -> TypeOrConstraint
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) -> TypeOrConstraint -> u
forall u. (forall d. Data d => d -> u) -> TypeOrConstraint -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeOrConstraint
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeOrConstraint -> c TypeOrConstraint
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeOrConstraint)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TypeOrConstraint)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeOrConstraint -> c TypeOrConstraint
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeOrConstraint -> c TypeOrConstraint
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeOrConstraint
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TypeOrConstraint
$ctoConstr :: TypeOrConstraint -> Constr
toConstr :: TypeOrConstraint -> Constr
$cdataTypeOf :: TypeOrConstraint -> DataType
dataTypeOf :: TypeOrConstraint -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeOrConstraint)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TypeOrConstraint)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TypeOrConstraint)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TypeOrConstraint)
$cgmapT :: (forall b. Data b => b -> b)
-> TypeOrConstraint -> TypeOrConstraint
gmapT :: (forall b. Data b => b -> b)
-> TypeOrConstraint -> TypeOrConstraint
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeOrConstraint -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TypeOrConstraint -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TypeOrConstraint -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TypeOrConstraint -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> TypeOrConstraint -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeOrConstraint -> m TypeOrConstraint
Data )
data NonStandardDefaultingStrategy
= DefaultNonStandardTyVars
| TryNotToDefaultNonStandardTyVars
data DefaultingStrategy
= DefaultKindVars
| NonStandardDefaulting NonStandardDefaultingStrategy
defaultNonStandardTyVars :: DefaultingStrategy -> Bool
defaultNonStandardTyVars :: DefaultingStrategy -> Bool
defaultNonStandardTyVars DefaultingStrategy
DefaultKindVars = Bool
True
defaultNonStandardTyVars (NonStandardDefaulting NonStandardDefaultingStrategy
DefaultNonStandardTyVars) = Bool
True
defaultNonStandardTyVars (NonStandardDefaulting NonStandardDefaultingStrategy
TryNotToDefaultNonStandardTyVars) = Bool
False
instance Outputable NonStandardDefaultingStrategy where
ppr :: NonStandardDefaultingStrategy -> SDoc
ppr NonStandardDefaultingStrategy
DefaultNonStandardTyVars = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"DefaultOnlyNonStandardTyVars"
ppr NonStandardDefaultingStrategy
TryNotToDefaultNonStandardTyVars = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"TryNotToDefaultNonStandardTyVars"
instance Outputable DefaultingStrategy where
ppr :: DefaultingStrategy -> SDoc
ppr DefaultingStrategy
DefaultKindVars = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"DefaultKindVars"
ppr (NonStandardDefaulting NonStandardDefaultingStrategy
ns) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"NonStandardDefaulting" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> NonStandardDefaultingStrategy -> SDoc
forall a. Outputable a => a -> SDoc
ppr NonStandardDefaultingStrategy
ns