Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
_L :: forall l e l e. Iso (GenLocated l e) (GenLocated l e) (l, e) (l, e) Source #
_HsModule :: forall name name. Iso (HsModule name) (HsModule name) (Maybe (Located ModuleName), Maybe (Located [LIE name]), [LImportDecl name], [LHsDecl name], Maybe (Located WarningTxt), Maybe LHsDocString) (Maybe (Located ModuleName), Maybe (Located [LIE name]), [LImportDecl name], [LHsDecl name], Maybe (Located WarningTxt), Maybe LHsDocString) Source #
_hsmodName :: forall name. Lens' (HsModule name) (Maybe (Located ModuleName)) Source #
_hsmodImports :: forall name. Lens' (HsModule name) [LImportDecl name] Source #
_hsmodHaddockModHeader :: forall name. Lens' (HsModule name) (Maybe LHsDocString) Source #
_hsmodDeprecMessage :: forall name. Lens' (HsModule name) (Maybe (Located WarningTxt)) Source #
_RoleAnnotD :: forall id. Prism' (HsDecl id) (RoleAnnotDecl id) Source #
_ClassDecl :: forall name. Prism' (TyClDecl name) (LHsContext name, Located name, LHsQTyVars name, [Located (FunDep (Located name))], [LSig name], LHsBinds name, [LFamilyDecl name], [LTyFamDefltEqn name], [LDocDecl], PostRn name NameSet) Source #
_DataDecl :: forall name. Prism' (TyClDecl name) (Located name, LHsQTyVars name, HsDataDefn name, PostRn name Bool, PostRn name NameSet) Source #
_SynDecl :: forall name. Prism' (TyClDecl name) (Located name, LHsQTyVars name, LHsType name, PostRn name NameSet) Source #
_tcdTyVars :: forall name. Traversal' (TyClDecl name) (LHsQTyVars name) Source #
_tcdFam :: forall name. Traversal' (TyClDecl name) (FamilyDecl name) Source #
_tcdDataDefn :: forall name. Traversal' (TyClDecl name) (HsDataDefn name) Source #
_tcdDataCusk :: forall name. Traversal' (TyClDecl name) (PostRn name Bool) Source #
_tcdCtxt :: forall name. Traversal' (TyClDecl name) (LHsContext name) Source #
_tcdATs :: forall name. Traversal' (TyClDecl name) [LFamilyDecl name] Source #
_tcdATDefs :: forall name. Traversal' (TyClDecl name) [LTyFamDefltEqn name] Source #
_TyFamInstD :: forall name. Prism' (InstDecl name) (TyFamInstDecl name) Source #
_DataFamInstD :: forall name. Prism' (InstDecl name) (DataFamInstDecl name) Source #
_tfid_inst :: forall name. Traversal' (InstDecl name) (TyFamInstDecl name) Source #
_dfid_inst :: forall name. Traversal' (InstDecl name) (DataFamInstDecl name) Source #
_cid_inst :: forall name. Traversal' (InstDecl name) (ClsInstDecl name) Source #
_DerivDecl :: forall name name. Iso (DerivDecl name) (DerivDecl name) (LHsSigType name, Maybe (Located OverlapMode)) (LHsSigType name, Maybe (Located OverlapMode)) Source #
_deriv_type :: forall name name. Lens (DerivDecl name) (DerivDecl name) (LHsSigType name) (LHsSigType name) Source #
_deriv_overlap_mode :: forall name. Lens' (DerivDecl name) (Maybe (Located OverlapMode)) Source #
_MinimalSig :: forall name. Prism' (Sig name) (SourceText, LBooleanFormula (Located name)) Source #
_SpecInstSig :: forall name. Prism' (Sig name) (SourceText, LHsSigType name) Source #
_SpecSig :: forall name. Prism' (Sig name) (Located name, [LHsSigType name], InlinePragma) Source #
_InlineSig :: forall name. Prism' (Sig name) (Located name, InlinePragma) Source #
_ClassOpSig :: forall name. Prism' (Sig name) (Bool, [Located name], LHsSigType name) Source #
_PatSynSig :: forall name. Prism' (Sig name) (Located name, LHsSigType name) Source #
_DefaultDecl :: forall name name. Iso (DefaultDecl name) (DefaultDecl name) [LHsType name] [LHsType name] Source #
_ForeignExport :: forall name. Prism' (ForeignDecl name) (Located name, LHsSigType name, PostTc name Coercion, ForeignExport) Source #
_ForeignImport :: forall name. Prism' (ForeignDecl name) (Located name, LHsSigType name, PostTc name Coercion, ForeignImport) Source #
_fd_sig_ty :: forall name. Lens' (ForeignDecl name) (LHsSigType name) Source #
_fd_fi :: forall name. Traversal' (ForeignDecl name) ForeignImport Source #
_fd_fe :: forall name. Traversal' (ForeignDecl name) ForeignExport Source #
_Warnings :: forall name name. Iso (WarnDecls name) (WarnDecls name) (SourceText, [LWarnDecl name]) (SourceText, [LWarnDecl name]) Source #
_wd_warnings :: forall name name. Lens (WarnDecls name) (WarnDecls name) [LWarnDecl name] [LWarnDecl name] Source #
_HsAnnotation :: forall name name. Iso (AnnDecl name) (AnnDecl name) (SourceText, AnnProvenance name, Located (HsExpr name)) (SourceText, AnnProvenance name, Located (HsExpr name)) Source #
_HsRules :: forall name name. Iso (RuleDecls name) (RuleDecls name) (SourceText, [LRuleDecl name]) (SourceText, [LRuleDecl name]) Source #
_rds_rules :: forall name name. Lens (RuleDecls name) (RuleDecls name) [LRuleDecl name] [LRuleDecl name] Source #
_HsVectInstIn :: forall name. Prism' (VectDecl name) (LHsSigType name) Source #
_HsVectClassIn :: forall name. Prism' (VectDecl name) (SourceText, Located name) Source #
_HsVectTypeIn :: forall name. Prism' (VectDecl name) (SourceText, Bool, Located name, Maybe (Located name)) Source #
_SpliceDecl :: forall id id. Iso (SpliceDecl id) (SpliceDecl id) (Located (HsSplice id), SpliceExplicitFlag) (Located (HsSplice id), SpliceExplicitFlag) Source #
_RoleAnnotDecl :: forall name name. Iso (RoleAnnotDecl name) (RoleAnnotDecl name) (Located name, [Located (Maybe Role)]) (Located name, [Located (Maybe Role)]) Source #
_PatSynBind :: forall idL idR. Prism' (HsBindLR idL idR) (PatSynBind idL idR) Source #
_AbsBindsSig :: forall idL idR. Prism' (HsBindLR idL idR) ([TyVar], [EvVar], idL, TcSpecPrags, TcEvBinds, LHsBind idL) Source #
_AbsBinds :: forall idL idR. Prism' (HsBindLR idL idR) ([TyVar], [EvVar], [ABExport idL], [TcEvBinds], LHsBinds idL) Source #
_PatBind :: forall idL idR. Prism' (HsBindLR idL idR) (LPat idL, GRHSs idR (LHsExpr idR), PostTc idR Type, PostRn idL NameSet, ([Tickish Id], [[Tickish Id]])) Source #
_FunBind :: forall idL idR. Prism' (HsBindLR idL idR) (Located idL, MatchGroup idR (LHsExpr idR), HsWrapper, PostRn idL NameSet, [Tickish Id]) Source #
_var_inline :: forall idL idR. Traversal' (HsBindLR idL idR) Bool Source #
_var_id :: forall idL idR. Traversal' (HsBindLR idL idR) idL Source #
_pat_ticks :: forall idL idR. Traversal' (HsBindLR idL idR) ([Tickish Id], [[Tickish Id]]) Source #
_pat_rhs_ty :: forall idL idR. Traversal' (HsBindLR idL idR) (PostTc idR Type) Source #
_fun_matches :: forall idL idR. Traversal' (HsBindLR idL idR) (MatchGroup idR (LHsExpr idR)) Source #
_fun_co_fn :: forall idL idR. Traversal' (HsBindLR idL idR) HsWrapper Source #
_abs_sig_prags :: forall idL idR. Traversal' (HsBindLR idL idR) TcSpecPrags Source #
_abs_sig_export :: forall idL idR. Traversal' (HsBindLR idL idR) idL Source #
_abs_sig_ev_bind :: forall idL idR. Traversal' (HsBindLR idL idR) TcEvBinds Source #
_abs_sig_bind :: forall idL idR. Traversal' (HsBindLR idL idR) (LHsBind idL) Source #
_abs_exports :: forall idL idR. Traversal' (HsBindLR idL idR) [ABExport idL] Source #
_abs_ev_vars :: forall idL idR. Traversal' (HsBindLR idL idR) [EvVar] Source #
_abs_ev_binds :: forall idL idR. Traversal' (HsBindLR idL idR) [TcEvBinds] Source #
_abs_binds :: forall idL idR. Traversal' (HsBindLR idL idR) (LHsBinds idL) Source #
_HsTickPragma :: forall id. Prism' (HsExpr id) (SourceText, (StringLiteral, (Int, Int), (Int, Int)), ((SourceText, SourceText), (SourceText, SourceText)), LHsExpr id) Source #
_HsArrApp :: forall id. Prism' (HsExpr id) (LHsExpr id, LHsExpr id, PostTc id Type, HsArrAppType, Bool) Source #
_HsTcBracketOut :: forall id. Prism' (HsExpr id) (HsBracket Name, [PendingTcSplice]) Source #
_HsRnBracketOut :: forall id. Prism' (HsExpr id) (HsBracket Name, [PendingRnSplice]) Source #
_HsCoreAnn :: forall id. Prism' (HsExpr id) (SourceText, StringLiteral, LHsExpr id) Source #
_HsSCC :: forall id. Prism' (HsExpr id) (SourceText, StringLiteral, LHsExpr id) Source #
_PArrSeq :: forall id. Prism' (HsExpr id) (PostTcExpr, ArithSeqInfo id) Source #
_ArithSeq :: forall id. Prism' (HsExpr id) (PostTcExpr, Maybe (SyntaxExpr id), ArithSeqInfo id) Source #
_ExprWithTySigOut :: forall id. Prism' (HsExpr id) (LHsExpr id, LHsSigWcType Name) Source #
_ExprWithTySig :: forall id. Prism' (HsExpr id) (LHsExpr id, LHsSigWcType id) Source #
_RecordUpd :: forall id. Prism' (HsExpr id) (LHsExpr id, [LHsRecUpdField id], PostTc id [ConLike], PostTc id [Type], PostTc id [Type], PostTc id HsWrapper) Source #
_RecordCon :: forall id. Prism' (HsExpr id) (Located id, PostTc id ConLike, PostTcExpr, HsRecordBinds id) Source #
_ExplicitList :: forall id. Prism' (HsExpr id) (PostTc id Type, Maybe (SyntaxExpr id), [LHsExpr id]) Source #
_HsDo :: forall id. Prism' (HsExpr id) (HsStmtContext Name, Located [ExprLStmt id], PostTc id Type) Source #
_HsIf :: forall id. Prism' (HsExpr id) (Maybe (SyntaxExpr id), LHsExpr id, LHsExpr id, LHsExpr id) Source #
_OpApp :: forall id. Prism' (HsExpr id) (LHsExpr id, LHsExpr id, PostRn id Fixity, LHsExpr id) Source #
_HsLamCase :: forall id. Prism' (HsExpr id) (PostTc id Type, MatchGroup id (LHsExpr id)) Source #
_HsOverLabel :: forall id. Prism' (HsExpr id) FastString Source #
_HsUnboundVar :: forall id. Prism' (HsExpr id) UnboundVar Source #
_rupd_wrap :: forall id. Traversal' (HsExpr id) (PostTc id HsWrapper) Source #
_rupd_out_tys :: forall id. Traversal' (HsExpr id) (PostTc id [Type]) Source #
_rupd_in_tys :: forall id. Traversal' (HsExpr id) (PostTc id [Type]) Source #
_rupd_flds :: forall id. Traversal' (HsExpr id) [LHsRecUpdField id] Source #
_rupd_expr :: forall id. Traversal' (HsExpr id) (LHsExpr id) Source #
_rupd_cons :: forall id. Traversal' (HsExpr id) (PostTc id [ConLike]) Source #
_rcon_flds :: forall id. Traversal' (HsExpr id) (HsRecordBinds id) Source #
_rcon_con_name :: forall id. Traversal' (HsExpr id) (Located id) Source #
_rcon_con_like :: forall id. Traversal' (HsExpr id) (PostTc id ConLike) Source #
_rcon_con_expr :: forall id. Traversal' (HsExpr id) PostTcExpr Source #
_SyntaxExpr :: forall id id. Iso (SyntaxExpr id) (SyntaxExpr id) (HsExpr id, [HsWrapper], HsWrapper) (HsExpr id, [HsWrapper], HsWrapper) Source #
_syn_res_wrap :: forall id. Lens' (SyntaxExpr id) HsWrapper Source #
_syn_expr :: forall id id. Lens (SyntaxExpr id) (SyntaxExpr id) (HsExpr id) (HsExpr id) Source #
_syn_arg_wraps :: forall id. Lens' (SyntaxExpr id) [HsWrapper] Source #
_MG :: forall id body id body. Iso (MatchGroup id body) (MatchGroup id body) (Located [LMatch id body], [PostTc id Type], PostTc id Type, Origin) (Located [LMatch id body], [PostTc id Type], PostTc id Type, Origin) Source #
_mg_res_ty :: forall id body. Lens' (MatchGroup id body) (PostTc id Type) Source #
_mg_origin :: forall id body. Lens' (MatchGroup id body) Origin Source #
_mg_arg_tys :: forall id body. Lens' (MatchGroup id body) [PostTc id Type] Source #
_mg_alts :: forall id body body. Lens (MatchGroup id body) (MatchGroup id body) (Located [LMatch id body]) (Located [LMatch id body]) Source #
_RecStmt :: forall idL idR body. Prism' (StmtLR idL idR body) ([LStmtLR idL idR body], [idR], [idR], SyntaxExpr idR, SyntaxExpr idR, SyntaxExpr idR, PostTc idR Type, [PostTcExpr], [PostTcExpr], PostTc idR Type) Source #
_TransStmt :: forall idL idR body. Prism' (StmtLR idL idR body) (TransForm, [ExprLStmt idL], [(idR, idR)], LHsExpr idR, Maybe (LHsExpr idR), SyntaxExpr idR, SyntaxExpr idR, PostTc idR Type, HsExpr idR) Source #
_ParStmt :: forall idL idR body. Prism' (StmtLR idL idR body) ([ParStmtBlock idL idR], HsExpr idR, SyntaxExpr idR, PostTc idR Type) Source #
_LetStmt :: forall idL idR body. Prism' (StmtLR idL idR body) (Located (HsLocalBindsLR idL idR)) Source #
_BodyStmt :: forall idL idR body. Prism' (StmtLR idL idR body) (body, SyntaxExpr idR, SyntaxExpr idR, PostTc idR Type) Source #
_ApplicativeStmt :: forall idL idR body. Prism' (StmtLR idL idR body) ([(SyntaxExpr idR, ApplicativeArg idL idR)], Maybe (SyntaxExpr idR), PostTc idR Type) Source #
_BindStmt :: forall idL idR body. Prism' (StmtLR idL idR body) (LPat idL, body, SyntaxExpr idR, SyntaxExpr idR, PostTc idR Type) Source #
_LastStmt :: forall idL idR body. Prism' (StmtLR idL idR body) (body, Bool, SyntaxExpr idR) Source #
_trS_using :: forall idL idR body. Traversal' (StmtLR idL idR body) (LHsExpr idR) Source #
_trS_stmts :: forall idL idR body. Traversal' (StmtLR idL idR body) [ExprLStmt idL] Source #
_trS_ret :: forall idL idR body. Traversal' (StmtLR idL idR body) (SyntaxExpr idR) Source #
_trS_bndrs :: forall idL idR body. Traversal' (StmtLR idL idR body) [(idR, idR)] Source #
_trS_bind_arg_ty :: forall idL idR body. Traversal' (StmtLR idL idR body) (PostTc idR Type) Source #
_trS_bind :: forall idL idR body. Traversal' (StmtLR idL idR body) (SyntaxExpr idR) Source #
_recS_stmts :: forall idL idR body. Traversal' (StmtLR idL idR body) [LStmtLR idL idR body] Source #
_recS_ret_ty :: forall idL idR body. Traversal' (StmtLR idL idR body) (PostTc idR Type) Source #
_recS_ret_fn :: forall idL idR body. Traversal' (StmtLR idL idR body) (SyntaxExpr idR) Source #
_recS_rec_rets :: forall idL idR body. Traversal' (StmtLR idL idR body) [PostTcExpr] Source #
_recS_rec_ids :: forall idL idR body. Traversal' (StmtLR idL idR body) [idR] Source #
_recS_mfix_fn :: forall idL idR body. Traversal' (StmtLR idL idR body) (SyntaxExpr idR) Source #
_recS_later_rets :: forall idL idR body. Traversal' (StmtLR idL idR body) [PostTcExpr] Source #
_recS_later_ids :: forall idL idR body. Traversal' (StmtLR idL idR body) [idR] Source #
_recS_bind_ty :: forall idL idR body. Traversal' (StmtLR idL idR body) (PostTc idR Type) Source #
_recS_bind_fn :: forall idL idR body. Traversal' (StmtLR idL idR body) (SyntaxExpr idR) Source #
_HsInteger :: Prism' HsLit (SourceText, Integer, Type) Source #
_HsWord64Prim :: Prism' HsLit (SourceText, Integer) Source #
_HsInt64Prim :: Prism' HsLit (SourceText, Integer) Source #
_HsWordPrim :: Prism' HsLit (SourceText, Integer) Source #
_HsIntPrim :: Prism' HsLit (SourceText, Integer) Source #
_HsString :: Prism' HsLit (SourceText, FastString) Source #
_HsCharPrim :: Prism' HsLit (SourceText, Char) Source #
_HsWildCardTy :: forall name. Prism' (HsType name) (HsWildCardInfo name) Source #
_HsExplicitTupleTy :: forall name. Prism' (HsType name) ([PostTc name Kind], [LHsType name]) Source #
_HsTupleTy :: forall name. Prism' (HsType name) (HsTupleSort, [LHsType name]) Source #
_HsForAllTy :: forall name. Prism' (HsType name) ([LHsTyVarBndr name], LHsType name) Source #
_hst_ctxt :: forall name. Traversal' (HsType name) (LHsContext name) Source #
_hst_bndrs :: forall name. Traversal' (HsType name) [LHsTyVarBndr name] Source #