Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- module Language.Haskell.Syntax.Binds
- data TcSpecPrag = SpecPrag Id HsWrapper InlinePragma
- type LTcSpecPrag = Located TcSpecPrag
- data TcSpecPrags
- data AnnSig = AnnSig {}
- newtype IdSig = IdSig {}
- data ABExport = ABE {}
- data AbsBinds = AbsBinds {
- abs_tvs :: [TyVar]
- abs_ev_vars :: [EvVar]
- abs_exports :: [ABExport]
- abs_ev_binds :: [TcEvBinds]
- abs_binds :: LHsBinds GhcTc
- abs_sig :: Bool
- data NHsValBindsLR idL = NValBinds [(RecFlag, LHsBinds idL)] [LSig GhcRn]
- pprLHsBinds :: (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- pprLHsBindsForUser :: (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc]
- pprDeclList :: [SDoc] -> SDoc
- emptyLocalBinds :: HsLocalBindsLR (GhcPass a) (GhcPass b)
- eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
- isEmptyValBinds :: HsValBindsLR (GhcPass a) (GhcPass b) -> Bool
- emptyValBindsIn :: HsValBindsLR (GhcPass a) (GhcPass b)
- emptyValBindsOut :: HsValBindsLR (GhcPass a) (GhcPass b)
- emptyLHsBinds :: LHsBindsLR (GhcPass idL) idR
- isEmptyLHsBinds :: LHsBindsLR (GhcPass idL) idR -> Bool
- plusHsValBinds :: HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a)
- ppr_monobind :: forall idL idR. (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc
- pprTicks :: SDoc -> SDoc -> SDoc
- isEmptyIPBindsPR :: HsIPBinds (GhcPass p) -> Bool
- isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool
- noSpecPrags :: TcSpecPrags
- hasSpecPrags :: TcSpecPrags -> Bool
- isDefaultMethod :: TcSpecPrags -> Bool
- ppr_sig :: forall p. OutputableBndrId p => Sig (GhcPass p) -> SDoc
- hsSigDoc :: forall p. IsPass p => Sig (GhcPass p) -> SDoc
- extractSpecPragName :: SourceText -> String
- pragBrackets :: SDoc -> SDoc
- pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc
- pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc
- pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc
- pprTcSpecPrags :: TcSpecPrags -> SDoc
- pprMinimalSig :: OutputableBndr name => LBooleanFormula (GenLocated l name) -> SDoc
Documentation
data TcSpecPrag Source #
Type checker Specification Pragma
SpecPrag Id HsWrapper InlinePragma | The Id to be specialised, a wrapper that specialises the polymorphic function, and inlining spec for the specialised function |
Instances
Data TcSpecPrag Source # | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrag -> c TcSpecPrag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrag # toConstr :: TcSpecPrag -> Constr # dataTypeOf :: TcSpecPrag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrag) # gmapT :: (forall b. Data b => b -> b) -> TcSpecPrag -> TcSpecPrag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r # gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # | |
Outputable TcSpecPrag Source # | |
Defined in GHC.Hs.Binds ppr :: TcSpecPrag -> SDoc Source # |
type LTcSpecPrag = Located TcSpecPrag Source #
Located Type checker Specification Pragmas
data TcSpecPrags Source #
Type checker Specialisation Pragmas
TcSpecPrags
conveys SPECIALISE
pragmas from the type checker to the desugarer
IsDefaultMethod | Super-specialised: a default method should be macro-expanded at every call site |
SpecPrags [LTcSpecPrag] |
Instances
Data TcSpecPrags Source # | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrags -> c TcSpecPrags # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrags # toConstr :: TcSpecPrags -> Constr # dataTypeOf :: TcSpecPrags -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrags) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrags) # gmapT :: (forall b. Data b => b -> b) -> TcSpecPrags -> TcSpecPrags # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r # gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrags -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrags -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # |
Instances
Data AnnSig Source # | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnSig -> c AnnSig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnSig # toConstr :: AnnSig -> Constr # dataTypeOf :: AnnSig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnSig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnSig) # gmapT :: (forall b. Data b => b -> b) -> AnnSig -> AnnSig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnSig -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnSig -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnSig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnSig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnSig -> m AnnSig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnSig -> m AnnSig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnSig -> m AnnSig # |
A type signature in generated code, notably the code generated for record selectors. We simply record the desired Id itself, replete with its name, type and IdDetails. Otherwise it's just like a type signature: there should be an accompanying binding
Instances
Data IdSig Source # | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IdSig -> c IdSig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IdSig # dataTypeOf :: IdSig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IdSig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IdSig) # gmapT :: (forall b. Data b => b -> b) -> IdSig -> IdSig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IdSig -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IdSig -> r # gmapQ :: (forall d. Data d => d -> u) -> IdSig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IdSig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IdSig -> m IdSig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IdSig -> m IdSig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IdSig -> m IdSig # |
Abstraction Bindings Export
Instances
Data ABExport Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport -> c ABExport # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ABExport # toConstr :: ABExport -> Constr # dataTypeOf :: ABExport -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ABExport) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ABExport) # gmapT :: (forall b. Data b => b -> b) -> ABExport -> ABExport # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport -> r # gmapQ :: (forall d. Data d => d -> u) -> ABExport -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport -> m ABExport # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport -> m ABExport # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport -> m ABExport # | |
Outputable ABExport Source # | |
Typechecked, generalised bindings, used in the output to the type checker. See Note [AbsBinds].
AbsBinds | |
|
Instances
Data AbsBinds Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbsBinds -> c AbsBinds # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AbsBinds # toConstr :: AbsBinds -> Constr # dataTypeOf :: AbsBinds -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AbsBinds) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AbsBinds) # gmapT :: (forall b. Data b => b -> b) -> AbsBinds -> AbsBinds # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbsBinds -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbsBinds -> r # gmapQ :: (forall d. Data d => d -> u) -> AbsBinds -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AbsBinds -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbsBinds -> m AbsBinds # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbsBinds -> m AbsBinds # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbsBinds -> m AbsBinds # |
data NHsValBindsLR idL Source #
Instances
Data (NHsValBindsLR GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcPs -> c (NHsValBindsLR GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcPs) # toConstr :: NHsValBindsLR GhcPs -> Constr # dataTypeOf :: NHsValBindsLR GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcPs -> NHsValBindsLR GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) # | |
Data (NHsValBindsLR GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcRn -> c (NHsValBindsLR GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcRn) # toConstr :: NHsValBindsLR GhcRn -> Constr # dataTypeOf :: NHsValBindsLR GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcRn -> NHsValBindsLR GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) # | |
Data (NHsValBindsLR GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcTc -> c (NHsValBindsLR GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcTc) # toConstr :: NHsValBindsLR GhcTc -> Constr # dataTypeOf :: NHsValBindsLR GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcTc -> NHsValBindsLR GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) # |
pprLHsBinds :: (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc Source #
pprLHsBindsForUser :: (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc] Source #
pprDeclList :: [SDoc] -> SDoc Source #
emptyLocalBinds :: HsLocalBindsLR (GhcPass a) (GhcPass b) Source #
eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool Source #
isEmptyValBinds :: HsValBindsLR (GhcPass a) (GhcPass b) -> Bool Source #
emptyValBindsIn :: HsValBindsLR (GhcPass a) (GhcPass b) Source #
emptyValBindsOut :: HsValBindsLR (GhcPass a) (GhcPass b) Source #
emptyLHsBinds :: LHsBindsLR (GhcPass idL) idR Source #
isEmptyLHsBinds :: LHsBindsLR (GhcPass idL) idR -> Bool Source #
plusHsValBinds :: HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) Source #
ppr_monobind :: forall idL idR. (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc Source #
hasSpecPrags :: TcSpecPrags -> Bool Source #
isDefaultMethod :: TcSpecPrags -> Bool Source #
extractSpecPragName :: SourceText -> String Source #
Extracts the name for a SPECIALIZE instance pragma. In hsSigDoc
, the src
field of SpecInstSig
signature contains the SourceText for a SPECIALIZE
instance pragma of the form: "SourceText {-# SPECIALIZE"
Extraction ensures that all variants of the pragma name (with a Z
or an
S
) are output exactly as used in the pragma.
pragBrackets :: SDoc -> SDoc Source #
pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc Source #
Using SourceText in case the pragma was spelled differently or used mixed case
pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc Source #
pprTcSpecPrags :: TcSpecPrags -> SDoc Source #
pprMinimalSig :: OutputableBndr name => LBooleanFormula (GenLocated l name) -> SDoc Source #
Orphan instances
OutputableBndrId p => Outputable (FixitySig (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsIPBinds (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (IPBind (GhcPass p)) Source # | |
Outputable (XRec a RdrName) => Outputable (RecordPatSynField a) Source # | |
ppr :: RecordPatSynField a -> SDoc Source # | |
OutputableBndrId p => Outputable (Sig (GhcPass p)) Source # | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) Source # | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) Source # | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) Source # | |
(OutputableBndrId l, OutputableBndrId r) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) Source # | |