haskell-tools-ast-0.2.0.0: Haskell AST for efficient tooling

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.References

Documentation

modImports :: forall dom stage. Lens (Module dom stage) (Module dom stage) (AnnList ImportDecl dom stage) (AnnList ImportDecl dom stage) Source #

modHead :: forall dom stage. Lens (Module dom stage) (Module dom stage) (AnnMaybe ModuleHead dom stage) (AnnMaybe ModuleHead dom stage) Source #

modDecl :: forall dom stage. Lens (Module dom stage) (Module dom stage) (AnnList Decl dom stage) (AnnList Decl dom stage) Source #

filePragmas :: forall dom stage. Lens (Module dom stage) (Module dom stage) (AnnList FilePragma dom stage) (AnnList FilePragma dom stage) Source #

mhPragma :: forall dom stage. Lens (ModuleHead dom stage) (ModuleHead dom stage) (AnnMaybe ModulePragma dom stage) (AnnMaybe ModulePragma dom stage) Source #

mhName :: forall dom stage. Lens (ModuleHead dom stage) (ModuleHead dom stage) (Ann ModuleName dom stage) (Ann ModuleName dom stage) Source #

mhExports :: forall dom stage. Lens (ModuleHead dom stage) (ModuleHead dom stage) (AnnMaybe ExportSpecList dom stage) (AnnMaybe ExportSpecList dom stage) Source #

espExports :: forall dom stage dom' stage'. Lens (ExportSpecList dom stage) (ExportSpecList dom' stage') (AnnList ExportSpec dom stage) (AnnList ExportSpec dom' stage') Source #

exportModuleName :: forall dom stage. Partial (ExportSpec dom stage) (ExportSpec dom stage) (Ann ModuleName dom stage) (Ann ModuleName dom stage) Source #

exportDecl :: forall dom stage. Partial (ExportSpec dom stage) (ExportSpec dom stage) (Ann IESpec dom stage) (Ann IESpec dom stage) Source #

ieSubspec :: forall dom stage. Lens (IESpec dom stage) (IESpec dom stage) (AnnMaybe SubSpec dom stage) (AnnMaybe SubSpec dom stage) Source #

ieName :: forall dom stage. Lens (IESpec dom stage) (IESpec dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

essList :: forall dom stage dom' stage'. Partial (SubSpec dom stage) (SubSpec dom' stage') (AnnList Name dom stage) (AnnList Name dom' stage') Source #

modWarningStr :: forall dom stage. Partial (ModulePragma dom stage) (ModulePragma dom stage) (AnnList StringNode dom stage) (AnnList StringNode dom stage) Source #

modDeprecatedPragma :: forall dom stage. Partial (ModulePragma dom stage) (ModulePragma dom stage) (AnnList StringNode dom stage) (AnnList StringNode dom stage) Source #

importSpec :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (AnnMaybe ImportSpec dom stage) (AnnMaybe ImportSpec dom stage) Source #

importSource :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (AnnMaybe ImportSource dom stage) (AnnMaybe ImportSource dom stage) Source #

importSafe :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (AnnMaybe ImportSafe dom stage) (AnnMaybe ImportSafe dom stage) Source #

importQualified :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (AnnMaybe ImportQualified dom stage) (AnnMaybe ImportQualified dom stage) Source #

importPkg :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (AnnMaybe StringNode dom stage) (AnnMaybe StringNode dom stage) Source #

importModule :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (Ann ModuleName dom stage) (Ann ModuleName dom stage) Source #

importAs :: forall dom stage. Lens (ImportDecl dom stage) (ImportDecl dom stage) (AnnMaybe ImportRenaming dom stage) (AnnMaybe ImportRenaming dom stage) Source #

importSpecList :: forall dom stage. Partial (ImportSpec dom stage) (ImportSpec dom stage) (AnnList IESpec dom stage) (AnnList IESpec dom stage) Source #

importSpecHiding :: forall dom stage. Partial (ImportSpec dom stage) (ImportSpec dom stage) (AnnList IESpec dom stage) (AnnList IESpec dom stage) Source #

importRename :: forall dom stage dom' stage'. Lens (ImportRenaming dom stage) (ImportRenaming dom' stage') (Ann ModuleName dom stage) (Ann ModuleName dom' stage') Source #

declValBind :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann ValueBind dom stage) (Ann ValueBind dom stage) Source #

declTypes :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnList Type dom stage) (AnnList Type dom stage) Source #

declTypeSig :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann TypeSignature dom stage) (Ann TypeSignature dom stage) Source #

declTypeFamily :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann TypeFamily dom stage) (Ann TypeFamily dom stage) Source #

declType :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

declSplice :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann Splice dom stage) (Ann Splice dom stage) Source #

declSafety :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe Safety dom stage) (AnnMaybe Safety dom stage) Source #

declRoles :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnList Role dom stage) (AnnList Role dom stage) Source #

declRoleType :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann QualifiedName dom stage) (Ann QualifiedName dom stage) Source #

declPragma :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann TopLevelPragma dom stage) (Ann TopLevelPragma dom stage) Source #

declPatTypeSig :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann PatternTypeSignature dom stage) (Ann PatternTypeSignature dom stage) Source #

declPatSyn :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann PatternSynonym dom stage) (Ann PatternSynonym dom stage) Source #

declOverlap :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe OverlapPragma dom stage) (AnnMaybe OverlapPragma dom stage) Source #

declNewtype :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann DataOrNewtypeKeyword dom stage) (Ann DataOrNewtypeKeyword dom stage) Source #

declName :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

declKind :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe KindConstraint dom stage) (AnnMaybe KindConstraint dom stage) Source #

declInstance :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann InstanceRule dom stage) (Ann InstanceRule dom stage) Source #

declInstRule :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann InstanceRule dom stage) (Ann InstanceRule dom stage) Source #

declInstDecl :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe InstBody dom stage) (AnnMaybe InstBody dom stage) Source #

declHead :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann DeclHead dom stage) (Ann DeclHead dom stage) Source #

declGadt :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnList GadtConDecl dom stage) (AnnList GadtConDecl dom stage) Source #

declFunDeps :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe FunDeps dom stage) (AnnMaybe FunDeps dom stage) Source #

declFixity :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann FixitySignature dom stage) (Ann FixitySignature dom stage) Source #

declDeriving :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe Deriving dom stage) (AnnMaybe Deriving dom stage) Source #

declDecl :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnList TypeEqn dom stage) (AnnList TypeEqn dom stage) Source #

declCtx :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe Context dom stage) (AnnMaybe Context dom stage) Source #

declCons :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnList ConDecl dom stage) (AnnList ConDecl dom stage) Source #

declCallConv :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann CallConv dom stage) (Ann CallConv dom stage) Source #

declBody :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (AnnMaybe ClassBody dom stage) (AnnMaybe ClassBody dom stage) Source #

declAssignedType :: forall dom stage. Partial (Decl dom stage) (Decl dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

cbElements :: forall dom stage dom' stage'. Lens (ClassBody dom stage) (ClassBody dom' stage') (AnnList ClassElement dom stage) (AnnList ClassElement dom' stage') Source #

pragmaFormula :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann MinimalFormula dom stage) (Ann MinimalFormula dom stage) Source #

ceTypeSig :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann TypeSignature dom stage) (Ann TypeSignature dom stage) Source #

ceTypeFam :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann TypeFamily dom stage) (Ann TypeFamily dom stage) Source #

ceType :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

cePatSig :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann PatternTypeSignature dom stage) (Ann PatternTypeSignature dom stage) Source #

ceName :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

ceKind :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

ceHead :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann DeclHead dom stage) (Ann DeclHead dom stage) Source #

ceBind :: forall dom stage. Partial (ClassElement dom stage) (ClassElement dom stage) (Ann ValueBind dom stage) (Ann ValueBind dom stage) Source #

dhRight :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann TyVar dom stage) (Ann TyVar dom stage) Source #

dhOperator :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

dhName :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

dhLeft :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann TyVar dom stage) (Ann TyVar dom stage) Source #

dhBody :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann DeclHead dom stage) (Ann DeclHead dom stage) Source #

dhAppOperand :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann TyVar dom stage) (Ann TyVar dom stage) Source #

dhAppFun :: forall dom stage. Partial (DeclHead dom stage) (DeclHead dom stage) (Ann DeclHead dom stage) (Ann DeclHead dom stage) Source #

instBodyDecls :: forall dom stage dom' stage'. Lens (InstBody dom stage) (InstBody dom' stage') (AnnList InstBodyDecl dom stage) (AnnList InstBodyDecl dom' stage') Source #

specializeInstanceType :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

instBodyTypeSig :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann TypeSignature dom stage) (Ann TypeSignature dom stage) Source #

instBodyTypeEqn :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann TypeEqn dom stage) (Ann TypeEqn dom stage) Source #

instBodyPatSyn :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann PatternSynonym dom stage) (Ann PatternSynonym dom stage) Source #

instBodyLhsType :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann InstanceRule dom stage) (Ann InstanceRule dom stage) Source #

instBodyGadtCons :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (AnnList GadtConDecl dom stage) (AnnList GadtConDecl dom stage) Source #

instBodyDerivings :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (AnnMaybe Deriving dom stage) (AnnMaybe Deriving dom stage) Source #

instBodyDeclFunbind :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann ValueBind dom stage) (Ann ValueBind dom stage) Source #

instBodyDataNew :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (Ann DataOrNewtypeKeyword dom stage) (Ann DataOrNewtypeKeyword dom stage) Source #

instBodyDataKind :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (AnnMaybe KindConstraint dom stage) (AnnMaybe KindConstraint dom stage) Source #

instBodyDataCons :: forall dom stage. Partial (InstBodyDecl dom stage) (InstBodyDecl dom stage) (AnnList ConDecl dom stage) (AnnList ConDecl dom stage) Source #

gadtConType :: forall dom stage. Lens (GadtConDecl dom stage) (GadtConDecl dom stage) (Ann GadtConType dom stage) (Ann GadtConType dom stage) Source #

gadtConNames :: forall dom stage. Lens (GadtConDecl dom stage) (GadtConDecl dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

gadtConResultType :: forall dom stage. Partial (GadtConType dom stage) (GadtConType dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

gadtConRecordFields :: forall dom stage. Partial (GadtConType dom stage) (GadtConType dom stage) (AnnList FieldDecl dom stage) (AnnList FieldDecl dom stage) Source #

gadtConNormalType :: forall dom stage. Partial (GadtConType dom stage) (GadtConType dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

funDeps :: forall dom stage dom' stage'. Lens (FunDeps dom stage) (FunDeps dom' stage') (AnnList FunDep dom stage) (AnnList FunDep dom' stage') Source #

funDepRhs :: forall dom stage. Lens (FunDep dom stage) (FunDep dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

funDepLhs :: forall dom stage. Lens (FunDep dom stage) (FunDep dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

conDeclRhs :: forall dom stage. Partial (ConDecl dom stage) (ConDecl dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

conDeclOp :: forall dom stage. Partial (ConDecl dom stage) (ConDecl dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

conDeclName :: forall dom stage. Partial (ConDecl dom stage) (ConDecl dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

conDeclLhs :: forall dom stage. Partial (ConDecl dom stage) (ConDecl dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

conDeclFields :: forall dom stage. Partial (ConDecl dom stage) (ConDecl dom stage) (AnnList FieldDecl dom stage) (AnnList FieldDecl dom stage) Source #

conDeclArgs :: forall dom stage. Partial (ConDecl dom stage) (ConDecl dom stage) (AnnList Type dom stage) (AnnList Type dom stage) Source #

fieldType :: forall dom stage. Lens (FieldDecl dom stage) (FieldDecl dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

fieldNames :: forall dom stage. Lens (FieldDecl dom stage) (FieldDecl dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

oneDerived :: forall dom stage. Partial (Deriving dom stage) (Deriving dom stage) (Ann InstanceHead dom stage) (Ann InstanceHead dom stage) Source #

allDerived :: forall dom stage. Partial (Deriving dom stage) (Deriving dom stage) (AnnList InstanceHead dom stage) (AnnList InstanceHead dom stage) Source #

irVars :: forall dom stage. Partial (InstanceRule dom stage) (InstanceRule dom stage) (AnnMaybe (AnnList TyVar) dom stage) (AnnMaybe (AnnList TyVar) dom stage) Source #

irRule :: forall dom stage. Partial (InstanceRule dom stage) (InstanceRule dom stage) (Ann InstanceRule dom stage) (Ann InstanceRule dom stage) Source #

irHead :: forall dom stage. Partial (InstanceRule dom stage) (InstanceRule dom stage) (Ann InstanceHead dom stage) (Ann InstanceHead dom stage) Source #

irCtx :: forall dom stage. Partial (InstanceRule dom stage) (InstanceRule dom stage) (AnnMaybe Context dom stage) (AnnMaybe Context dom stage) Source #

ihType :: forall dom stage. Partial (InstanceHead dom stage) (InstanceHead dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

ihOperator :: forall dom stage. Partial (InstanceHead dom stage) (InstanceHead dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

ihLeftOp :: forall dom stage. Partial (InstanceHead dom stage) (InstanceHead dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

ihHead :: forall dom stage. Partial (InstanceHead dom stage) (InstanceHead dom stage) (Ann InstanceHead dom stage) (Ann InstanceHead dom stage) Source #

ihFun :: forall dom stage. Partial (InstanceHead dom stage) (InstanceHead dom stage) (Ann InstanceHead dom stage) (Ann InstanceHead dom stage) Source #

ihConName :: forall dom stage. Partial (InstanceHead dom stage) (InstanceHead dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

teRhs :: forall dom stage. Lens (TypeEqn dom stage) (TypeEqn dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

teLhs :: forall dom stage. Lens (TypeEqn dom stage) (TypeEqn dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

kindConstr :: forall dom stage dom' stage'. Lens (KindConstraint dom stage) (KindConstraint dom' stage') (Ann Kind dom stage) (Ann Kind dom' stage') Source #

tyVarName :: forall dom stage. Lens (TyVar dom stage) (TyVar dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

tyVarKind :: forall dom stage. Lens (TyVar dom stage) (TyVar dom stage) (AnnMaybe KindConstraint dom stage) (AnnMaybe KindConstraint dom stage) Source #

typeWildcardName :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

typeType :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeRight :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeResult :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeQQ :: forall dom stage. Partial (Type dom stage) (Type dom stage) (QuasiQuote dom stage) (QuasiQuote dom stage) Source #

typeParam :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeOperator :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

typeName :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

typeLeft :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeKind :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

typeInner :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeElements :: forall dom stage. Partial (Type dom stage) (Type dom stage) (AnnList Type dom stage) (AnnList Type dom stage) Source #

typeElement :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeCtx :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Context dom stage) (Ann Context dom stage) Source #

typeCon :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

typeBounded :: forall dom stage. Partial (Type dom stage) (Type dom stage) (AnnList TyVar dom stage) (AnnList TyVar dom stage) Source #

typeArg :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

tsSplice :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Splice dom stage) (Splice dom stage) Source #

tpPromoted :: forall dom stage. Partial (Type dom stage) (Type dom stage) (Ann (Promoted Type) dom stage) (Ann (Promoted Type) dom stage) Source #

kindVar :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

kindRight :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

kindPromoted :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann (Promoted Kind) dom stage) (Ann (Promoted Kind) dom stage) Source #

kindParen :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

kindLeft :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

kindElem :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

kindAppFun :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

kindAppArg :: forall dom stage. Partial (Kind dom stage) (Kind dom stage) (Ann Kind dom stage) (Ann Kind dom stage) Source #

contextAssertions :: forall dom stage. Partial (Context dom stage) (Context dom stage) (AnnList Assertion dom stage) (AnnList Assertion dom stage) Source #

contextAssertion :: forall dom stage. Partial (Context dom stage) (Context dom stage) (Ann Assertion dom stage) (Ann Assertion dom stage) Source #

assertTypes :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (AnnList Type dom stage) (AnnList Type dom stage) Source #

assertRhs :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

assertOp :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

assertLhs :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

assertImplVar :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

assertImplType :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

assertClsName :: forall dom stage. Partial (Assertion dom stage) (Assertion dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

tupleSectionElems :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList TupSecElem dom stage) (AnnList TupSecElem dom stage) Source #

tupleElems :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList Expr dom stage) (AnnList Expr dom stage) Source #

quotedName :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

procPattern :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

procExpr :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Cmd dom stage) (Ann Cmd dom stage) Source #

listElems :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList Expr dom stage) (AnnList Expr dom stage) Source #

innerExpr :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Splice dom stage) (Ann Splice dom stage) Source #

exprType :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

exprThen :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprStmts :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList Stmt dom stage) (AnnList Stmt dom stage) Source #

exprSig :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

exprRhs :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprRecName :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

exprRecFields :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList FieldUpdate dom stage) (AnnList FieldUpdate dom stage) Source #

exprQQ :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann QuasiQuote dom stage) (Ann QuasiQuote dom stage) Source #

exprPragma :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann ExprPragma dom stage) (Ann ExprPragma dom stage) Source #

exprOperator :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

exprName :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

exprLit :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Literal dom stage) (Ann Literal dom stage) Source #

exprLhs :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprInner :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprIfAlts :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList GuardedCaseRhs dom stage) (AnnList GuardedCaseRhs dom stage) Source #

exprFunBind :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList LocalBind dom stage) (AnnList LocalBind dom stage) Source #

exprFun :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprElse :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprCond :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprCase :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprBindings :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList Pattern dom stage) (AnnList Pattern dom stage) Source #

exprArg :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

exprAlts :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList Alt dom stage) (AnnList Alt dom stage) Source #

enumToFix :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

enumTo :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnMaybe Expr dom stage) (AnnMaybe Expr dom stage) Source #

enumThen :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnMaybe Expr dom stage) (AnnMaybe Expr dom stage) Source #

enumFrom :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

doKind :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann DoKind dom stage) (Ann DoKind dom stage) Source #

compExpr :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

compBody :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (AnnList ListCompBody dom stage) (AnnList ListCompBody dom stage) Source #

bracket :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann Bracket dom stage) (Ann Bracket dom stage) Source #

arrowAppl :: forall dom stage. Partial (Expr dom stage) (Expr dom stage) (Ann ArrowAppl dom stage) (Ann ArrowAppl dom stage) Source #

stmtPattern :: forall expr dom stage. Partial (Stmt' expr dom stage) (Stmt' expr dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

stmtExpr :: forall expr dom stage. Partial (Stmt' expr dom stage) (Stmt' expr dom stage) (Ann expr dom stage) (Ann expr dom stage) Source #

stmtBinds :: forall expr dom stage. Partial (Stmt' expr dom stage) (Stmt' expr dom stage) (AnnList LocalBind dom stage) (AnnList LocalBind dom stage) Source #

cmdStmtBinds :: forall expr dom stage. Partial (Stmt' expr dom stage) (Stmt' expr dom stage) (AnnList (Stmt' expr) dom stage) (AnnList (Stmt' expr) dom stage) Source #

usingExpr :: forall dom stage. Partial (CompStmt dom stage) (CompStmt dom stage) (AnnMaybe Expr dom stage) (AnnMaybe Expr dom stage) Source #

thenExpr :: forall dom stage. Partial (CompStmt dom stage) (CompStmt dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

compStmt :: forall dom stage. Partial (CompStmt dom stage) (CompStmt dom stage) (Ann Stmt dom stage) (Ann Stmt dom stage) Source #

byExpr :: forall dom stage. Partial (CompStmt dom stage) (CompStmt dom stage) (AnnMaybe Expr dom stage) (AnnMaybe Expr dom stage) Source #

valBindRhs :: forall dom stage. Partial (ValueBind dom stage) (ValueBind dom stage) (Ann Rhs dom stage) (Ann Rhs dom stage) Source #

valBindPat :: forall dom stage. Partial (ValueBind dom stage) (ValueBind dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

valBindLocals :: forall dom stage. Partial (ValueBind dom stage) (ValueBind dom stage) (AnnMaybe LocalBinds dom stage) (AnnMaybe LocalBinds dom stage) Source #

funBindMatches :: forall dom stage. Partial (ValueBind dom stage) (ValueBind dom stage) (AnnList Match dom stage) (AnnList Match dom stage) Source #

patternType :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

patternSplice :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Splice dom stage) (Ann Splice dom stage) Source #

patternRhs :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

patternOperator :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

patternName :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

patternLiteral :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Literal dom stage) (Ann Literal dom stage) Source #

patternLit :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Literal dom stage) (Ann Literal dom stage) Source #

patternLhs :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

patternInner :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

patternFields :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (AnnList PatternField dom stage) (AnnList PatternField dom stage) Source #

patternExpr :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

patternElems :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (AnnList Pattern dom stage) (AnnList Pattern dom stage) Source #

patternArgs :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (AnnList Pattern dom stage) (AnnList Pattern dom stage) Source #

patQQ :: forall dom stage. Partial (Pattern dom stage) (Pattern dom stage) (Ann QuasiQuote dom stage) (Ann QuasiQuote dom stage) Source #

fieldPatternWildcard :: forall dom stage. Partial (PatternField dom stage) (PatternField dom stage) (Ann FieldWildcard dom stage) (Ann FieldWildcard dom stage) Source #

fieldPatternName :: forall dom stage. Partial (PatternField dom stage) (PatternField dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

fieldPattern :: forall dom stage. Partial (PatternField dom stage) (PatternField dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

spliceId :: forall dom stage. Partial (Splice dom stage) (Splice dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

spliceExpr :: forall dom stage. Partial (Splice dom stage) (Splice dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

qqString :: forall dom stage. Lens (QQString dom stage) (QQString dom stage) String String Source #

matchRhs :: forall dom stage. Lens (Match dom stage) (Match dom stage) (Ann Rhs dom stage) (Ann Rhs dom stage) Source #

matchLhs :: forall dom stage. Lens (Match dom stage) (Match dom stage) (Ann MatchLhs dom stage) (Ann MatchLhs dom stage) Source #

matchBinds :: forall dom stage. Lens (Match dom stage) (Match dom stage) (AnnMaybe LocalBinds dom stage) (AnnMaybe LocalBinds dom stage) Source #

altRhs :: forall expr dom stage expr'. Lens (Alt' expr dom stage) (Alt' expr' dom stage) (Ann (CaseRhs' expr) dom stage) (Ann (CaseRhs' expr') dom stage) Source #

altPattern :: forall expr dom stage. Lens (Alt' expr dom stage) (Alt' expr dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

altBinds :: forall expr dom stage. Lens (Alt' expr dom stage) (Alt' expr dom stage) (AnnMaybe LocalBinds dom stage) (AnnMaybe LocalBinds dom stage) Source #

rhsGuards :: forall dom stage. Partial (Rhs dom stage) (Rhs dom stage) (AnnList GuardedRhs dom stage) (AnnList GuardedRhs dom stage) Source #

rhsExpr :: forall dom stage. Partial (Rhs dom stage) (Rhs dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

guardStmts :: forall dom stage. Lens (GuardedRhs dom stage) (GuardedRhs dom stage) (AnnList RhsGuard dom stage) (AnnList RhsGuard dom stage) Source #

guardExpr :: forall dom stage. Lens (GuardedRhs dom stage) (GuardedRhs dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

fieldWildcard :: forall dom stage. Partial (FieldUpdate dom stage) (FieldUpdate dom stage) (Ann FieldWildcard dom stage) (Ann FieldWildcard dom stage) Source #

fieldValue :: forall dom stage. Partial (FieldUpdate dom stage) (FieldUpdate dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

fieldUpdateName :: forall dom stage. Partial (FieldUpdate dom stage) (FieldUpdate dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

fieldName :: forall dom stage. Partial (FieldUpdate dom stage) (FieldUpdate dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

bracketType :: forall dom stage. Partial (Bracket dom stage) (Bracket dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

bracketPattern :: forall dom stage. Partial (Bracket dom stage) (Bracket dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

bracketExpr :: forall dom stage. Partial (Bracket dom stage) (Bracket dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

bracketDecl :: forall dom stage. Partial (Bracket dom stage) (Bracket dom stage) (AnnList Decl dom stage) (AnnList Decl dom stage) Source #

specializeType :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (AnnList Type dom stage) (AnnList Type dom stage) Source #

specializeDef :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

pragmaRule :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (AnnList Rule dom stage) (AnnList Rule dom stage) Source #

pragmaPhase :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (AnnMaybe PhaseControl dom stage) (AnnMaybe PhaseControl dom stage) Source #

pragmaObjects :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

pragmaMessage :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann StringNode dom stage) (Ann StringNode dom stage) Source #

pragmaLineNum :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann LineNumber dom stage) (Ann LineNumber dom stage) Source #

pragmaFileName :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (AnnMaybe StringNode dom stage) (AnnMaybe StringNode dom stage) Source #

pragmaConlike :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (AnnMaybe ConlikeAnnot dom stage) (AnnMaybe ConlikeAnnot dom stage) Source #

noInlineDef :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

inlineDef :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

inlinableDef :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

annotationSubject :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann AnnotationSubject dom stage) (Ann AnnotationSubject dom stage) Source #

annotateExpr :: forall dom stage. Partial (TopLevelPragma dom stage) (TopLevelPragma dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

ruleRhs :: forall dom stage. Lens (Rule dom stage) (Rule dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

rulePhase :: forall dom stage. Lens (Rule dom stage) (Rule dom stage) (AnnMaybe PhaseControl dom stage) (AnnMaybe PhaseControl dom stage) Source #

ruleName :: forall dom stage. Lens (Rule dom stage) (Rule dom stage) (Ann StringNode dom stage) (Ann StringNode dom stage) Source #

ruleLhs :: forall dom stage. Lens (Rule dom stage) (Rule dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

ruleBounded :: forall dom stage. Lens (Rule dom stage) (Rule dom stage) (AnnList TyVar dom stage) (AnnList TyVar dom stage) Source #

annotateName :: forall dom stage dom' stage'. Partial (AnnotationSubject dom stage) (AnnotationSubject dom' stage') (Ann Name dom stage) (Ann Name dom' stage') Source #

minimalOrs :: forall dom stage. Partial (MinimalFormula dom stage) (MinimalFormula dom stage) (AnnList MinimalFormula dom stage) (AnnList MinimalFormula dom stage) Source #

minimalName :: forall dom stage. Partial (MinimalFormula dom stage) (MinimalFormula dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

minimalInner :: forall dom stage. Partial (MinimalFormula dom stage) (MinimalFormula dom stage) (Ann MinimalFormula dom stage) (Ann MinimalFormula dom stage) Source #

minimalAnds :: forall dom stage. Partial (MinimalFormula dom stage) (MinimalFormula dom stage) (AnnList MinimalFormula dom stage) (AnnList MinimalFormula dom stage) Source #

pragmaStr :: forall dom stage. Partial (ExprPragma dom stage) (ExprPragma dom stage) (Ann StringNode dom stage) (Ann StringNode dom stage) Source #

pragmaSrcRange :: forall dom stage. Partial (ExprPragma dom stage) (ExprPragma dom stage) (Ann SourceRange dom stage) (Ann SourceRange dom stage) Source #

srToLine :: forall dom stage. Lens (SourceRange dom stage) (SourceRange dom stage) (Ann Number dom stage) (Ann Number dom stage) Source #

srToCol :: forall dom stage. Lens (SourceRange dom stage) (SourceRange dom stage) (Ann Number dom stage) (Ann Number dom stage) Source #

srFromLine :: forall dom stage. Lens (SourceRange dom stage) (SourceRange dom stage) (Ann Number dom stage) (Ann Number dom stage) Source #

srFromCol :: forall dom stage. Lens (SourceRange dom stage) (SourceRange dom stage) (Ann Number dom stage) (Ann Number dom stage) Source #

srFileName :: forall dom stage. Lens (SourceRange dom stage) (SourceRange dom stage) (Ann StringNode dom stage) (Ann StringNode dom stage) Source #

numberInteger :: forall dom stage. Lens (Number dom stage) (Number dom stage) Integer Integer Source #

qqExprName :: forall dom stage. Lens (QuasiQuote dom stage) (QuasiQuote dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

qqExprBody :: forall dom stage. Lens (QuasiQuote dom stage) (QuasiQuote dom stage) (Ann QQString dom stage) (Ann QQString dom stage) Source #

guardRhs :: forall dom stage. Partial (RhsGuard dom stage) (RhsGuard dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

guardPat :: forall dom stage. Partial (RhsGuard dom stage) (RhsGuard dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

guardCheck :: forall dom stage. Partial (RhsGuard dom stage) (RhsGuard dom stage) (Ann Expr dom stage) (Ann Expr dom stage) Source #

guardBinds :: forall dom stage. Partial (RhsGuard dom stage) (RhsGuard dom stage) (AnnList LocalBind dom stage) (AnnList LocalBind dom stage) Source #

localVal :: forall dom stage. Partial (LocalBind dom stage) (LocalBind dom stage) (Ann ValueBind dom stage) (Ann ValueBind dom stage) Source #

localSig :: forall dom stage. Partial (LocalBind dom stage) (LocalBind dom stage) (Ann TypeSignature dom stage) (Ann TypeSignature dom stage) Source #

localFixity :: forall dom stage. Partial (LocalBind dom stage) (LocalBind dom stage) (Ann FixitySignature dom stage) (Ann FixitySignature dom stage) Source #

localBinds :: forall dom stage dom' stage'. Lens (LocalBinds dom stage) (LocalBinds dom' stage') (AnnList LocalBind dom stage) (AnnList LocalBind dom' stage') Source #

fixityPrecedence :: forall dom stage. Lens (FixitySignature dom stage) (FixitySignature dom stage) (Ann Precedence dom stage) (Ann Precedence dom stage) Source #

fixityOperators :: forall dom stage. Lens (FixitySignature dom stage) (FixitySignature dom stage) (AnnList Operator dom stage) (AnnList Operator dom stage) Source #

fixityAssoc :: forall dom stage. Lens (FixitySignature dom stage) (FixitySignature dom stage) (Ann Assoc dom stage) (Ann Assoc dom stage) Source #

tsType :: forall dom stage. Lens (TypeSignature dom stage) (TypeSignature dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

tsName :: forall dom stage. Lens (TypeSignature dom stage) (TypeSignature dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

compStmts :: forall dom stage dom' stage'. Lens (ListCompBody dom stage) (ListCompBody dom' stage') (AnnList CompStmt dom stage) (AnnList CompStmt dom' stage') Source #

tupSecExpr :: forall dom stage dom' stage'. Partial (TupSecElem dom stage) (TupSecElem dom' stage') (Ann Expr dom stage) (Ann Expr dom' stage') Source #

tfSpec :: forall dom stage. Partial (TypeFamily dom stage) (TypeFamily dom stage) (AnnMaybe TypeFamilySpec dom stage) (AnnMaybe TypeFamilySpec dom stage) Source #

tfKind :: forall dom stage. Partial (TypeFamily dom stage) (TypeFamily dom stage) (AnnMaybe KindConstraint dom stage) (AnnMaybe KindConstraint dom stage) Source #

tfHead :: forall dom stage. Lens (TypeFamily dom stage) (TypeFamily dom stage) (Ann DeclHead dom stage) (Ann DeclHead dom stage) Source #

tfSpecKind :: forall dom stage. Partial (TypeFamilySpec dom stage) (TypeFamilySpec dom stage) (Ann KindConstraint dom stage) (Ann KindConstraint dom stage) Source #

tfInjectivity :: forall dom stage. Partial (TypeFamilySpec dom stage) (TypeFamilySpec dom stage) (Ann InjectivityAnn dom stage) (Ann InjectivityAnn dom stage) Source #

injAnnRes :: forall dom stage. Lens (InjectivityAnn dom stage) (InjectivityAnn dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

injAnnDeps :: forall dom stage. Lens (InjectivityAnn dom stage) (InjectivityAnn dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

rhsCaseGuards :: forall expr dom stage. Partial (CaseRhs' expr dom stage) (CaseRhs' expr dom stage) (AnnList (GuardedCaseRhs' expr) dom stage) (AnnList (GuardedCaseRhs' expr) dom stage) Source #

rhsCaseExpr :: forall expr dom stage. Partial (CaseRhs' expr dom stage) (CaseRhs' expr dom stage) (Ann expr dom stage) (Ann expr dom stage) Source #

caseGuardStmts :: forall expr dom stage. Lens (GuardedCaseRhs' expr dom stage) (GuardedCaseRhs' expr dom stage) (AnnList RhsGuard dom stage) (AnnList RhsGuard dom stage) Source #

caseGuardExpr :: forall expr dom stage expr'. Lens (GuardedCaseRhs' expr dom stage) (GuardedCaseRhs' expr' dom stage) (Ann expr dom stage) (Ann expr' dom stage) Source #

patRhs :: forall dom stage. Lens (PatternSynonym dom stage) (PatternSynonym dom stage) (Ann PatSynRhs dom stage) (Ann PatSynRhs dom stage) Source #

patLhs :: forall dom stage. Lens (PatternSynonym dom stage) (PatternSynonym dom stage) (Ann PatSynLhs dom stage) (Ann PatSynLhs dom stage) Source #

patRhsOpposite :: forall dom stage. Partial (PatSynRhs dom stage) (PatSynRhs dom stage) (AnnMaybe PatSynWhere dom stage) (AnnMaybe PatSynWhere dom stage) Source #

patRhsPat :: forall dom stage. Lens (PatSynRhs dom stage) (PatSynRhs dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

patSynRhs :: forall dom stage. Partial (PatSynLhs dom stage) (PatSynLhs dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

patSynOp :: forall dom stage. Partial (PatSynLhs dom stage) (PatSynLhs dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

patSynLhs :: forall dom stage. Partial (PatSynLhs dom stage) (PatSynLhs dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

patName :: forall dom stage. Partial (PatSynLhs dom stage) (PatSynLhs dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

patArgs :: forall dom stage. Partial (PatSynLhs dom stage) (PatSynLhs dom stage) (AnnList Name dom stage) (AnnList Name dom stage) Source #

patOpposite :: forall dom stage dom' stage'. Lens (PatSynWhere dom stage) (PatSynWhere dom' stage') (AnnList Match dom stage) (AnnList Match dom' stage') Source #

patSigType :: forall dom stage. Lens (PatternTypeSignature dom stage) (PatternTypeSignature dom stage) (Ann Type dom stage) (Ann Type dom stage) Source #

patSigName :: forall dom stage. Lens (PatternTypeSignature dom stage) (PatternTypeSignature dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

langExt :: forall dom stage. Lens (LanguageExtension dom stage) (LanguageExtension dom stage) String String Source #

matchLhsRhs :: forall dom stage. Partial (MatchLhs dom stage) (MatchLhs dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

matchLhsOperator :: forall dom stage. Partial (MatchLhs dom stage) (MatchLhs dom stage) (Ann Operator dom stage) (Ann Operator dom stage) Source #

matchLhsName :: forall dom stage. Partial (MatchLhs dom stage) (MatchLhs dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

matchLhsLhs :: forall dom stage. Partial (MatchLhs dom stage) (MatchLhs dom stage) (Ann Pattern dom stage) (Ann Pattern dom stage) Source #

matchLhsArgs :: forall dom stage. Lens (MatchLhs dom stage) (MatchLhs dom stage) (AnnList Pattern dom stage) (AnnList Pattern dom stage) Source #

stringLitValue :: forall dom stage. Partial (Literal dom stage) (Literal dom stage) String String Source #

intLitValue :: forall dom stage. Partial (Literal dom stage) (Literal dom stage) Integer Integer Source #

fracLitValue :: forall dom stage. Partial (Literal dom stage) (Literal dom stage) Rational Rational Source #

floatLitValue :: forall dom stage. Partial (Literal dom stage) (Literal dom stage) Rational Rational Source #

charLitValue :: forall dom stage. Partial (Literal dom stage) (Literal dom stage) Char Char Source #

promotedStringValue :: forall t dom stage. Partial (Promoted t dom stage) (Promoted t dom stage) String String Source #

promotedIntValue :: forall t dom stage. Partial (Promoted t dom stage) (Promoted t dom stage) Integer Integer Source #

promotedElements :: forall t dom stage t'. Partial (Promoted t dom stage) (Promoted t' dom stage) (AnnList t dom stage) (AnnList t' dom stage) Source #

promotedConName :: forall t dom stage. Partial (Promoted t dom stage) (Promoted t dom stage) (Ann Name dom stage) (Ann Name dom stage) Source #

operatorName :: forall dom stage dom' stage'. Lens (Operator dom stage) (Operator dom' stage') (Ann QualifiedName dom stage) (Ann QualifiedName dom' stage') Source #

simpleName :: forall dom stage dom' stage'. Lens (Name dom stage) (Name dom' stage') (Ann QualifiedName dom stage) (Ann QualifiedName dom' stage') Source #

unqualifiedName :: forall dom stage. Lens (QualifiedName dom stage) (QualifiedName dom stage) (Ann UnqualName dom stage) (Ann UnqualName dom stage) Source #

qualifiers :: forall dom stage. Lens (QualifiedName dom stage) (QualifiedName dom stage) (AnnList UnqualName dom stage) (AnnList UnqualName dom stage) Source #

moduleNameString :: forall dom stage. Lens (ModuleName dom stage) (ModuleName dom stage) String String Source #

simpleNameStr :: forall dom stage. Lens (UnqualName dom stage) (UnqualName dom stage) String String Source #

stringNodeStr :: forall dom stage. Lens (StringNode dom stage) (StringNode dom stage) String String Source #

precedenceValue :: forall dom stage. Lens (Precedence dom stage) (Precedence dom stage) Int Int Source #

phaseUntil :: forall dom stage. Lens (PhaseControl dom stage) (PhaseControl dom stage) (AnnMaybe PhaseInvert dom stage) (AnnMaybe PhaseInvert dom stage) Source #

phaseNumber :: forall dom stage. Lens (PhaseControl dom stage) (PhaseControl dom stage) (Ann PhaseNumber dom stage) (Ann PhaseNumber dom stage) Source #

phaseNum :: forall dom stage. Lens (PhaseNumber dom stage) (PhaseNumber dom stage) Integer Integer Source #