| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Tc.Gen.Sig
Synopsis
- data TcSigInfo
 - data TcIdSigInfo
- = CompleteSig { }
 - | PartialSig { }
 
 - data TcIdSigInst
 - data TcPatSynInfo = TPSI {}
 - type TcSigFun = Name -> Maybe TcSigInfo
 - isPartialSig :: TcIdSigInst -> Bool
 - hasCompleteSig :: TcSigFun -> Name -> Bool
 - tcIdSigName :: TcIdSigInfo -> Name
 - tcSigInfoName :: TcSigInfo -> Name
 - completeSigPolyId_maybe :: TcSigInfo -> Maybe TcId
 - isCompleteHsSig :: LHsSigWcType GhcRn -> Bool
 - lhsSigWcTypeContextSpan :: LHsSigWcType GhcRn -> ReportRedundantConstraints
 - lhsSigTypeContextSpan :: LHsSigType GhcRn -> ReportRedundantConstraints
 - tcTySigs :: [LSig GhcRn] -> TcM ([TcId], TcSigFun)
 - tcUserTypeSig :: SrcSpan -> LHsSigWcType GhcRn -> Maybe Name -> TcM TcIdSigInfo
 - completeSigFromId :: UserTypeCtxt -> Id -> TcIdSigInfo
 - tcInstSig :: TcIdSigInfo -> TcM TcIdSigInst
 - type TcPragEnv = NameEnv [LSig GhcRn]
 - emptyPragEnv :: TcPragEnv
 - lookupPragEnv :: TcPragEnv -> Name -> [LSig GhcRn]
 - extendPragEnv :: TcPragEnv -> (Name, LSig GhcRn) -> TcPragEnv
 - mkPragEnv :: [LSig GhcRn] -> LHsBinds GhcRn -> TcPragEnv
 - tcSpecPrags :: Id -> [LSig GhcRn] -> TcM [LTcSpecPrag]
 - tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper
 - tcImpPrags :: [LSig GhcRn] -> TcM [LTcSpecPrag]
 - addInlinePrags :: TcId -> [LSig GhcRn] -> TcM TcId
 - addInlinePragArity :: Arity -> LSig GhcRn -> LSig GhcRn
 
Documentation
Constructors
| TcIdSig TcIdSigInfo | |
| TcPatSynSig TcPatSynInfo | 
Instances
data TcIdSigInfo Source #
Constructors
| CompleteSig | |
| PartialSig | |
Fields 
  | |
Instances
| Outputable TcIdSigInfo Source # | |
Defined in GHC.Tc.Types.BasicTypes Methods ppr :: TcIdSigInfo -> SDoc Source #  | |
data TcIdSigInst Source #
Instances
| Outputable TcIdSigInst Source # | |
Defined in GHC.Tc.Types.BasicTypes Methods ppr :: TcIdSigInst -> SDoc Source #  | |
data TcPatSynInfo Source #
Constructors
| TPSI | |
Fields  | |
Instances
| Outputable TcPatSynInfo Source # | |
Defined in GHC.Tc.Types.BasicTypes Methods ppr :: TcPatSynInfo -> SDoc Source #  | |
isPartialSig :: TcIdSigInst -> Bool Source #
tcIdSigName :: TcIdSigInfo -> Name Source #
tcSigInfoName :: TcSigInfo -> Name Source #
isCompleteHsSig :: LHsSigWcType GhcRn -> Bool Source #
If there are no wildcards, return a LHsSigWcType
lhsSigWcTypeContextSpan :: LHsSigWcType GhcRn -> ReportRedundantConstraints Source #
Find the location of the top-level context of a HsType. For example:
  forall a b. (Eq a, Ord b) => blah
              ^^^^^^^^^^^^^
If there is none, return Nothing
tcUserTypeSig :: SrcSpan -> LHsSigWcType GhcRn -> Maybe Name -> TcM TcIdSigInfo Source #
completeSigFromId :: UserTypeCtxt -> Id -> TcIdSigInfo Source #
tcInstSig :: TcIdSigInfo -> TcM TcIdSigInst Source #
tcSpecPrags :: Id -> [LSig GhcRn] -> TcM [LTcSpecPrag] Source #
tcSpecWrapper :: UserTypeCtxt -> TcType -> TcType -> TcM HsWrapper Source #
tcImpPrags :: [LSig GhcRn] -> TcM [LTcSpecPrag] Source #