haskell-src-exts-prisms-1.18.2.0: Prisms with newtype wrappers for haskell-src-exts

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Exts.Prisms

Documentation

_VarFormula :: forall l. Prism' (BooleanFormula l) (l, Name l) Source #

_ModuleAnn :: forall l. Prism' (Annotation l) (l, Exp l) Source #

_TypeAnn :: forall l. Prism' (Annotation l) (l, Name l, Exp l) Source #

_Ann :: forall l. Prism' (Annotation l) (l, Name l, Exp l) Source #

_ActiveUntil :: forall l. Prism' (Activation l) (l, Int) Source #

_ActiveFrom :: forall l. Prism' (Activation l) (l, Int) Source #

_TypedRuleVar :: forall l. Prism' (RuleVar l) (l, Name l, Type l) Source #

_RuleVar :: forall l. Prism' (RuleVar l) (l, Name l) Source #

_Rule :: forall l l. Iso (Rule l) (Rule l) (l, String, Maybe (Activation l), Maybe [RuleVar l], Exp l, Exp l) (l, String, Maybe (Activation l), Maybe [RuleVar l], Exp l, Exp l) Source #

_Incoherent :: forall l. Prism' (Overlap l) l Source #

_Overlap :: forall l. Prism' (Overlap l) l Source #

_NoOverlap :: forall l. Prism' (Overlap l) l Source #

_LanguagePragma :: forall l. Prism' (ModulePragma l) (l, [Name l]) Source #

_CApi :: forall l. Prism' (CallConv l) l Source #

_JavaScript :: forall l. Prism' (CallConv l) l Source #

_Js :: forall l. Prism' (CallConv l) l Source #

_Jvm :: forall l. Prism' (CallConv l) l Source #

_DotNet :: forall l. Prism' (CallConv l) l Source #

_CPlusPlus :: forall l. Prism' (CallConv l) l Source #

_CCall :: forall l. Prism' (CallConv l) l Source #

_StdCall :: forall l. Prism' (CallConv l) l Source #

_PlaySafe :: forall l. Prism' (Safety l) (l, Bool) Source #

_PlayRisky :: forall l. Prism' (Safety l) l Source #

_ParenSplice :: forall l. Prism' (Splice l) (l, Exp l) Source #

_IdSplice :: forall l. Prism' (Splice l) (l, String) Source #

_DeclBracket :: forall l. Prism' (Bracket l) (l, [Decl l]) Source #

_TypeBracket :: forall l. Prism' (Bracket l) (l, Type l) Source #

_PatBracket :: forall l. Prism' (Bracket l) (l, Pat l) Source #

_ExpBracket :: forall l. Prism' (Bracket l) (l, Exp l) Source #

_RoleWildcard :: forall l. Prism' (Role l) l Source #

_Phantom :: forall l. Prism' (Role l) l Source #

_Representational :: forall l. Prism' (Role l) l Source #

_Nominal :: forall l. Prism' (Role l) l Source #

_XDomName :: forall l. Prism' (XName l) (l, String, String) Source #

_XName :: forall l. Prism' (XName l) (l, String) Source #

_IPLin :: forall l. Prism' (IPName l) (l, String) Source #

_IPDup :: forall l. Prism' (IPName l) (l, String) Source #

_ConName :: forall l. Prism' (CName l) (l, Name l) Source #

_VarName :: forall l. Prism' (CName l) (l, Name l) Source #

_Cons :: forall l. Prism' (SpecialCon l) l Source #

_TupleCon :: forall l. Prism' (SpecialCon l) (l, Boxed, Int) Source #

_FunCon :: forall l. Prism' (SpecialCon l) l Source #

_ListCon :: forall l. Prism' (SpecialCon l) l Source #

_UnitCon :: forall l. Prism' (SpecialCon l) l Source #

_ConOp :: forall l. Prism' (Op l) (l, Name l) Source #

_VarOp :: forall l. Prism' (Op l) (l, Name l) Source #

_QConOp :: forall l. Prism' (QOp l) (l, QName l) Source #

_QVarOp :: forall l. Prism' (QOp l) (l, QName l) Source #

_Symbol :: forall l. Prism' (Name l) (l, String) Source #

_Ident :: forall l. Prism' (Name l) (l, String) Source #

_Special :: forall l. Prism' (QName l) (l, SpecialCon l) Source #

_UnQual :: forall l. Prism' (QName l) (l, Name l) Source #

_Qual :: forall l. Prism' (QName l) (l, ModuleName l, Name l) Source #

_ModuleName :: forall l l. Iso (ModuleName l) (ModuleName l) (l, String) (l, String) Source #

_Negative :: forall l. Prism' (Sign l) l Source #

_Signless :: forall l. Prism' (Sign l) l Source #

_PrimString :: forall l. Prism' (Literal l) (l, String, String) Source #

_PrimChar :: forall l. Prism' (Literal l) (l, Char, String) Source #

_PrimWord :: forall l. Prism' (Literal l) (l, Integer, String) Source #

_PrimInt :: forall l. Prism' (Literal l) (l, Integer, String) Source #

_Frac :: forall l. Prism' (Literal l) (l, Rational, String) Source #

_Int :: forall l. Prism' (Literal l) (l, Integer, String) Source #

_String :: forall l. Prism' (Literal l) (l, String, String) Source #

_Char :: forall l. Prism' (Literal l) (l, Char, String) Source #

_RPOptG :: forall l. Prism' (RPatOp l) l Source #

_RPOpt :: forall l. Prism' (RPatOp l) l Source #

_RPPlusG :: forall l. Prism' (RPatOp l) l Source #

_RPPlus :: forall l. Prism' (RPatOp l) l Source #

_RPStarG :: forall l. Prism' (RPatOp l) l Source #

_RPStar :: forall l. Prism' (RPatOp l) l Source #

_RPPat :: forall l. Prism' (RPat l) (l, Pat l) Source #

_RPParen :: forall l. Prism' (RPat l) (l, RPat l) Source #

_RPAs :: forall l. Prism' (RPat l) (l, Name l, RPat l) Source #

_RPCAs :: forall l. Prism' (RPat l) (l, Name l, RPat l) Source #

_RPGuard :: forall l. Prism' (RPat l) (l, Pat l, [Stmt l]) Source #

_RPSeq :: forall l. Prism' (RPat l) (l, [RPat l]) Source #

_RPEither :: forall l. Prism' (RPat l) (l, RPat l, RPat l) Source #

_RPOp :: forall l. Prism' (RPat l) (l, RPat l, RPatOp l) Source #

_PXAttr :: forall l l. Iso (PXAttr l) (PXAttr l) (l, XName l, Pat l) (l, XName l, Pat l) Source #

_PFieldPun :: forall l. Prism' (PatField l) (l, QName l) Source #

_PFieldPat :: forall l. Prism' (PatField l) (l, QName l, Pat l) Source #

_PBangPat :: forall l. Prism' (Pat l) (l, Pat l) Source #

_PQuasiQuote :: forall l. Prism' (Pat l) (l, String, String) Source #

_PXRPats :: forall l. Prism' (Pat l) (l, [RPat l]) Source #

_PXPatTag :: forall l. Prism' (Pat l) (l, Pat l) Source #

_PXPcdata :: forall l. Prism' (Pat l) (l, String) Source #

_PXETag :: forall l. Prism' (Pat l) (l, XName l, [PXAttr l], Maybe (Pat l)) Source #

_PXTag :: forall l. Prism' (Pat l) (l, XName l, [PXAttr l], Maybe (Pat l), [Pat l]) Source #

_PRPat :: forall l. Prism' (Pat l) (l, [RPat l]) Source #

_PViewPat :: forall l. Prism' (Pat l) (l, Exp l, Pat l) Source #

_PatTypeSig :: forall l. Prism' (Pat l) (l, Pat l, Type l) Source #

_PIrrPat :: forall l. Prism' (Pat l) (l, Pat l) Source #

_PWildCard :: forall l. Prism' (Pat l) l Source #

_PAsPat :: forall l. Prism' (Pat l) (l, Name l, Pat l) Source #

_PRec :: forall l. Prism' (Pat l) (l, QName l, [PatField l]) Source #

_PParen :: forall l. Prism' (Pat l) (l, Pat l) Source #

_PList :: forall l. Prism' (Pat l) (l, [Pat l]) Source #

_PTuple :: forall l. Prism' (Pat l) (l, Boxed, [Pat l]) Source #

_PApp :: forall l. Prism' (Pat l) (l, QName l, [Pat l]) Source #

_PInfixApp :: forall l. Prism' (Pat l) (l, Pat l, QName l, Pat l) Source #

_PNPlusK :: forall l. Prism' (Pat l) (l, Name l, Integer) Source #

_PLit :: forall l. Prism' (Pat l) (l, Sign l, Literal l) Source #

_PVar :: forall l. Prism' (Pat l) (l, Name l) Source #

_XAttr :: forall l l. Iso (XAttr l) (XAttr l) (l, XName l, Exp l) (l, XName l, Exp l) Source #

_Alt :: forall l l. Iso (Alt l) (Alt l) (l, Pat l, Rhs l, Maybe (Binds l)) (l, Pat l, Rhs l, Maybe (Binds l)) Source #

_FieldPun :: forall l. Prism' (FieldUpdate l) (l, QName l) Source #

_FieldUpdate :: forall l. Prism' (FieldUpdate l) (l, QName l, Exp l) Source #

_GroupByUsing :: forall l. Prism' (QualStmt l) (l, Exp l, Exp l) Source #

_GroupUsing :: forall l. Prism' (QualStmt l) (l, Exp l) Source #

_GroupBy :: forall l. Prism' (QualStmt l) (l, Exp l) Source #

_ThenBy :: forall l. Prism' (QualStmt l) (l, Exp l, Exp l) Source #

_ThenTrans :: forall l. Prism' (QualStmt l) (l, Exp l) Source #

_QualStmt :: forall l. Prism' (QualStmt l) (l, Stmt l) Source #

_RecStmt :: forall l. Prism' (Stmt l) (l, [Stmt l]) Source #

_LetStmt :: forall l. Prism' (Stmt l) (l, Binds l) Source #

_Qualifier :: forall l. Prism' (Stmt l) (l, Exp l) Source #

_Generator :: forall l. Prism' (Stmt l) (l, Pat l, Exp l) Source #

_ExprHole :: forall l. Prism' (Exp l) l Source #

_LCase :: forall l. Prism' (Exp l) (l, [Alt l]) Source #

_RightArrHighApp :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_LeftArrHighApp :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_RightArrApp :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_LeftArrApp :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_Proc :: forall l. Prism' (Exp l) (l, Pat l, Exp l) Source #

_GenPragma :: forall l. Prism' (Exp l) (l, String, (Int, Int), (Int, Int), Exp l) Source #

_SCCPragma :: forall l. Prism' (Exp l) (l, String, Exp l) Source #

_CorePragma :: forall l. Prism' (Exp l) (l, String, Exp l) Source #

_XChildTag :: forall l. Prism' (Exp l) (l, [Exp l]) Source #

_XExpTag :: forall l. Prism' (Exp l) (l, Exp l) Source #

_XPcdata :: forall l. Prism' (Exp l) (l, String) Source #

_XETag :: forall l. Prism' (Exp l) (l, XName l, [XAttr l], Maybe (Exp l)) Source #

_XTag :: forall l. Prism' (Exp l) (l, XName l, [XAttr l], Maybe (Exp l), [Exp l]) Source #

_TypeApp :: forall l. Prism' (Exp l) (l, Type l) Source #

_QuasiQuote :: forall l. Prism' (Exp l) (l, String, String) Source #

_SpliceExp :: forall l. Prism' (Exp l) (l, Splice l) Source #

_BracketExp :: forall l. Prism' (Exp l) (l, Bracket l) Source #

_TypQuote :: forall l. Prism' (Exp l) (l, QName l) Source #

_VarQuote :: forall l. Prism' (Exp l) (l, QName l) Source #

_ExpTypeSig :: forall l. Prism' (Exp l) (l, Exp l, Type l) Source #

_ParArrayComp :: forall l. Prism' (Exp l) (l, Exp l, [[QualStmt l]]) Source #

_ParComp :: forall l. Prism' (Exp l) (l, Exp l, [[QualStmt l]]) Source #

_ListComp :: forall l. Prism' (Exp l) (l, Exp l, [QualStmt l]) Source #

_ParArrayFromThenTo :: forall l. Prism' (Exp l) (l, Exp l, Exp l, Exp l) Source #

_ParArrayFromTo :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_EnumFromThenTo :: forall l. Prism' (Exp l) (l, Exp l, Exp l, Exp l) Source #

_EnumFromThen :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_EnumFromTo :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_EnumFrom :: forall l. Prism' (Exp l) (l, Exp l) Source #

_RecUpdate :: forall l. Prism' (Exp l) (l, Exp l, [FieldUpdate l]) Source #

_RecConstr :: forall l. Prism' (Exp l) (l, QName l, [FieldUpdate l]) Source #

_RightSection :: forall l. Prism' (Exp l) (l, QOp l, Exp l) Source #

_LeftSection :: forall l. Prism' (Exp l) (l, Exp l, QOp l) Source #

_Paren :: forall l. Prism' (Exp l) (l, Exp l) Source #

_ParArray :: forall l. Prism' (Exp l) (l, [Exp l]) Source #

_List :: forall l. Prism' (Exp l) (l, [Exp l]) Source #

_TupleSection :: forall l. Prism' (Exp l) (l, Boxed, [Maybe (Exp l)]) Source #

_Tuple :: forall l. Prism' (Exp l) (l, Boxed, [Exp l]) Source #

_MDo :: forall l. Prism' (Exp l) (l, [Stmt l]) Source #

_Do :: forall l. Prism' (Exp l) (l, [Stmt l]) Source #

_Case :: forall l. Prism' (Exp l) (l, Exp l, [Alt l]) Source #

_MultiIf :: forall l. Prism' (Exp l) (l, [GuardedRhs l]) Source #

_If :: forall l. Prism' (Exp l) (l, Exp l, Exp l, Exp l) Source #

_Let :: forall l. Prism' (Exp l) (l, Binds l, Exp l) Source #

_Lambda :: forall l. Prism' (Exp l) (l, [Pat l], Exp l) Source #

_NegApp :: forall l. Prism' (Exp l) (l, Exp l) Source #

_App :: forall l. Prism' (Exp l) (l, Exp l, Exp l) Source #

_InfixApp :: forall l. Prism' (Exp l) (l, Exp l, QOp l, Exp l) Source #

_Lit :: forall l. Prism' (Exp l) (l, Literal l) Source #

_Con :: forall l. Prism' (Exp l) (l, QName l) Source #

_IPVar :: forall l. Prism' (Exp l) (l, IPName l) Source #

_OverloadedLabel :: forall l. Prism' (Exp l) (l, String) Source #

_Var :: forall l. Prism' (Exp l) (l, QName l) Source #

_TypeEqn :: forall l l. Iso (TypeEqn l) (TypeEqn l) (l, Type l, Type l) (l, Type l, Type l) Source #

_PromotedUnit :: forall l. Prism' (Promoted l) l Source #

_PromotedTuple :: forall l. Prism' (Promoted l) (l, [Type l]) Source #

_PromotedList :: forall l. Prism' (Promoted l) (l, Bool, [Type l]) Source #

_PromotedCon :: forall l. Prism' (Promoted l) (l, Bool, QName l) Source #

_UnkindedVar :: forall l. Prism' (TyVarBind l) (l, Name l) Source #

_KindedVar :: forall l. Prism' (TyVarBind l) (l, Name l, Kind l) Source #

_KindList :: forall l. Prism' (Kind l) (l, Kind l) Source #

_KindTuple :: forall l. Prism' (Kind l) (l, [Kind l]) Source #

_KindApp :: forall l. Prism' (Kind l) (l, Kind l, Kind l) Source #

_KindVar :: forall l. Prism' (Kind l) (l, QName l) Source #

_KindParen :: forall l. Prism' (Kind l) (l, Kind l) Source #

_KindFn :: forall l. Prism' (Kind l) (l, Kind l, Kind l) Source #

_KindStar :: forall l. Prism' (Kind l) l Source #

_TyQuasiQuote :: forall l. Prism' (Type l) (l, String, String) Source #

_TyWildCard :: forall l. Prism' (Type l) (l, Maybe (Name l)) Source #

_TyBang :: forall l. Prism' (Type l) (l, BangType l, Unpackedness l, Type l) Source #

_TySplice :: forall l. Prism' (Type l) (l, Splice l) Source #

_TyEquals :: forall l. Prism' (Type l) (l, Type l, Type l) Source #

_TyPromoted :: forall l. Prism' (Type l) (l, Promoted l) Source #

_TyKind :: forall l. Prism' (Type l) (l, Type l, Kind l) Source #

_TyInfix :: forall l. Prism' (Type l) (l, Type l, QName l, Type l) Source #

_TyParen :: forall l. Prism' (Type l) (l, Type l) Source #

_TyCon :: forall l. Prism' (Type l) (l, QName l) Source #

_TyVar :: forall l. Prism' (Type l) (l, Name l) Source #

_TyApp :: forall l. Prism' (Type l) (l, Type l, Type l) Source #

_TyParArray :: forall l. Prism' (Type l) (l, Type l) Source #

_TyList :: forall l. Prism' (Type l) (l, Type l) Source #

_TyTuple :: forall l. Prism' (Type l) (l, Boxed, [Type l]) Source #

_TyFun :: forall l. Prism' (Type l) (l, Type l, Type l) Source #

_TyForall :: forall l. Prism' (Type l) (l, Maybe [TyVarBind l], Maybe (Context l), Type l) Source #

_WildCardA :: forall l. Prism' (Asst l) (l, Maybe (Name l)) Source #

_ParenA :: forall l. Prism' (Asst l) (l, Asst l) Source #

_EqualP :: forall l. Prism' (Asst l) (l, Type l, Type l) Source #

_IParam :: forall l. Prism' (Asst l) (l, IPName l, Type l) Source #

_InfixA :: forall l. Prism' (Asst l) (l, Type l, QName l, Type l) Source #

_AppA :: forall l. Prism' (Asst l) (l, Name l, [Type l]) Source #

_ClassA :: forall l. Prism' (Asst l) (l, QName l, [Type l]) Source #

_FunDep :: forall l l. Iso (FunDep l) (FunDep l) (l, [Name l], [Name l]) (l, [Name l], [Name l]) Source #

_CxEmpty :: forall l. Prism' (Context l) l Source #

_CxTuple :: forall l. Prism' (Context l) (l, [Asst l]) Source #

_CxSingle :: forall l. Prism' (Context l) (l, Asst l) Source #

_GuardedRhs :: forall l l. Iso (GuardedRhs l) (GuardedRhs l) (l, [Stmt l], Exp l) (l, [Stmt l], Exp l) Source #

_GuardedRhss :: forall l. Prism' (Rhs l) (l, [GuardedRhs l]) Source #

_UnGuardedRhs :: forall l. Prism' (Rhs l) (l, Exp l) Source #

_InfixMatch :: forall l. Prism' (Match l) (l, Pat l, Name l, [Pat l], Rhs l, Maybe (Binds l)) Source #

_Match :: forall l. Prism' (Match l) (l, Name l, [Pat l], Rhs l, Maybe (Binds l)) Source #

_NoUnpack :: forall l. Prism' (Unpackedness l) l Source #

_Unpack :: forall l. Prism' (Unpackedness l) l Source #

_LazyTy :: forall l. Prism' (BangType l) l Source #

_BangedTy :: forall l. Prism' (BangType l) l Source #

_GadtDecl :: forall l l. Iso (GadtDecl l) (GadtDecl l) (l, Name l, Maybe [FieldDecl l], Type l) (l, Name l, Maybe [FieldDecl l], Type l) Source #

_FieldDecl :: forall l l. Iso (FieldDecl l) (FieldDecl l) (l, [Name l], Type l) (l, [Name l], Type l) Source #

_RecDecl :: forall l. Prism' (ConDecl l) (l, Name l, [FieldDecl l]) Source #

_InfixConDecl :: forall l. Prism' (ConDecl l) (l, Type l, Name l, Type l) Source #

_ConDecl :: forall l. Prism' (ConDecl l) (l, Name l, [Type l]) Source #

_NewType :: forall l. Prism' (DataOrNew l) l Source #

_DataType :: forall l. Prism' (DataOrNew l) l Source #

_Deriving :: forall l l. Iso (Deriving l) (Deriving l) (l, [InstRule l]) (l, [InstRule l]) Source #

_InsGData :: forall l. Prism' (InstDecl l) (l, DataOrNew l, Type l, Maybe (Kind l), [GadtDecl l], Maybe (Deriving l)) Source #

_InsData :: forall l. Prism' (InstDecl l) (l, DataOrNew l, Type l, [QualConDecl l], Maybe (Deriving l)) Source #

_InsType :: forall l. Prism' (InstDecl l) (l, Type l, Type l) Source #

_InsDecl :: forall l. Prism' (InstDecl l) (l, Decl l) Source #

_ClsDefSig :: forall l. Prism' (ClassDecl l) (l, Name l, Type l) Source #

_ClsTyDef :: forall l. Prism' (ClassDecl l) (l, TypeEqn l) Source #

_ClsDecl :: forall l. Prism' (ClassDecl l) (l, Decl l) Source #

_TyVarSig :: forall l. Prism' (ResultSig l) (l, TyVarBind l) Source #

_KindSig :: forall l. Prism' (ResultSig l) (l, Kind l) Source #

_InjectivityInfo :: forall l l. Iso (InjectivityInfo l) (InjectivityInfo l) (l, Name l, [Name l]) (l, Name l, [Name l]) Source #

_IPBind :: forall l l. Iso (IPBind l) (IPBind l) (l, IPName l, Exp l) (l, IPName l, Exp l) Source #

_IPBinds :: forall l. Prism' (Binds l) (l, [IPBind l]) Source #

_BDecls :: forall l. Prism' (Binds l) (l, [Decl l]) Source #

_IHApp :: forall l. Prism' (InstHead l) (l, InstHead l, Type l) Source #

_IHParen :: forall l. Prism' (InstHead l) (l, InstHead l) Source #

_IHInfix :: forall l. Prism' (InstHead l) (l, Type l, QName l) Source #

_IHCon :: forall l. Prism' (InstHead l) (l, QName l) Source #

_IParen :: forall l. Prism' (InstRule l) (l, InstRule l) Source #

_IRule :: forall l. Prism' (InstRule l) (l, Maybe [TyVarBind l], Maybe (Context l), InstHead l) Source #

_DHApp :: forall l. Prism' (DeclHead l) (l, DeclHead l, TyVarBind l) Source #

_DHParen :: forall l. Prism' (DeclHead l) (l, DeclHead l) Source #

_DHInfix :: forall l. Prism' (DeclHead l) (l, TyVarBind l, Name l) Source #

_DHead :: forall l. Prism' (DeclHead l) (l, Name l) Source #

_RoleAnnotDecl :: forall l. Prism' (Decl l) (l, QName l, [Role l]) Source #

_AnnPragma :: forall l. Prism' (Decl l) (l, Annotation l) Source #

_InstSig :: forall l. Prism' (Decl l) (l, InstRule l) Source #

_SpecInlineSig :: forall l. Prism' (Decl l) (l, Bool, Maybe (Activation l), QName l, [Type l]) Source #

_SpecSig :: forall l. Prism' (Decl l) (l, Maybe (Activation l), QName l, [Type l]) Source #

_InlineConlikeSig :: forall l. Prism' (Decl l) (l, Maybe (Activation l), QName l) Source #

_InlineSig :: forall l. Prism' (Decl l) (l, Bool, Maybe (Activation l), QName l) Source #

_WarnPragmaDecl :: forall l. Prism' (Decl l) (l, [([Name l], String)]) Source #

_DeprPragmaDecl :: forall l. Prism' (Decl l) (l, [([Name l], String)]) Source #

_RulePragmaDecl :: forall l. Prism' (Decl l) (l, [Rule l]) Source #

_ForExp :: forall l. Prism' (Decl l) (l, CallConv l, Maybe String, Name l, Type l) Source #

_ForImp :: forall l. Prism' (Decl l) (l, CallConv l, Maybe (Safety l), Maybe String, Name l, Type l) Source #

_PatSyn :: forall l. Prism' (Decl l) (l, Pat l, Pat l, PatternSynDirection l) Source #

_PatBind :: forall l. Prism' (Decl l) (l, Pat l, Rhs l, Maybe (Binds l)) Source #

_FunBind :: forall l. Prism' (Decl l) (l, [Match l]) Source #

_PatSynSig :: forall l. Prism' (Decl l) (l, Name l, Maybe [TyVarBind l], Maybe (Context l), Maybe (Context l), Type l) Source #

_TypeSig :: forall l. Prism' (Decl l) (l, [Name l], Type l) Source #

_SpliceDecl :: forall l. Prism' (Decl l) (l, Exp l) Source #

_DefaultDecl :: forall l. Prism' (Decl l) (l, [Type l]) Source #

_InfixDecl :: forall l. Prism' (Decl l) (l, Assoc l, Maybe Int, [Op l]) Source #

_DerivDecl :: forall l. Prism' (Decl l) (l, Maybe (Overlap l), InstRule l) Source #

_InstDecl :: forall l. Prism' (Decl l) (l, Maybe (Overlap l), InstRule l, Maybe [InstDecl l]) Source #

_ClassDecl :: forall l. Prism' (Decl l) (l, Maybe (Context l), DeclHead l, [FunDep l], Maybe [ClassDecl l]) Source #

_GDataInsDecl :: forall l. Prism' (Decl l) (l, DataOrNew l, Type l, Maybe (Kind l), [GadtDecl l], Maybe (Deriving l)) Source #

_DataInsDecl :: forall l. Prism' (Decl l) (l, DataOrNew l, Type l, [QualConDecl l], Maybe (Deriving l)) Source #

_TypeInsDecl :: forall l. Prism' (Decl l) (l, Type l, Type l) Source #

_DataFamDecl :: forall l. Prism' (Decl l) (l, Maybe (Context l), DeclHead l, Maybe (ResultSig l)) Source #

_GDataDecl :: forall l. Prism' (Decl l) (l, DataOrNew l, Maybe (Context l), DeclHead l, Maybe (Kind l), [GadtDecl l], Maybe (Deriving l)) Source #

_DataDecl :: forall l. Prism' (Decl l) (l, DataOrNew l, Maybe (Context l), DeclHead l, [QualConDecl l], Maybe (Deriving l)) Source #

_TypeDecl :: forall l. Prism' (Decl l) (l, DeclHead l, Type l) Source #

_NoNamespace :: forall l. Prism' (Namespace l) l Source #

_AssocRight :: forall l. Prism' (Assoc l) l Source #

_AssocLeft :: forall l. Prism' (Assoc l) l Source #

_AssocNone :: forall l. Prism' (Assoc l) l Source #

_IThingWith :: forall l. Prism' (ImportSpec l) (l, Name l, [CName l]) Source #

_IThingAll :: forall l. Prism' (ImportSpec l) (l, Name l) Source #

_IAbs :: forall l. Prism' (ImportSpec l) (l, Namespace l, Name l) Source #

_IVar :: forall l. Prism' (ImportSpec l) (l, Name l) Source #

_EWildcard :: forall l. Prism' (EWildcard l) (l, Int) Source #

_NoWildcard :: forall l. Prism' (EWildcard l) l Source #

_EThingWith :: forall l. Prism' (ExportSpec l) (l, EWildcard l, QName l, [CName l]) Source #

_EAbs :: forall l. Prism' (ExportSpec l) (l, Namespace l, QName l) Source #

_EVar :: forall l. Prism' (ExportSpec l) (l, QName l) Source #

_WarnText :: forall l. Prism' (WarningText l) (l, String) Source #

_DeprText :: forall l. Prism' (WarningText l) (l, String) Source #

_XmlHybrid :: forall l. Prism' (Module l) (l, Maybe (ModuleHead l), [ModulePragma l], [ImportDecl l], [Decl l], XName l, [XAttr l], Maybe (Exp l), [Exp l]) Source #

_XmlPage :: forall l. Prism' (Module l) (l, ModuleName l, [ModulePragma l], XName l, [XAttr l], Maybe (Exp l), [Exp l]) Source #

_Module :: forall l. Prism' (Module l) (l, Maybe (ModuleHead l), [ModulePragma l], [ImportDecl l], [Decl l]) Source #

newtype C_Module l Source #

Constructors

C_Module (l, Maybe (ModuleHead l), [ModulePragma l], [ImportDecl l], [Decl l]) 

Instances

Wrapped (C_Module l0) Source # 

Associated Types

type Unwrapped (C_Module l0) :: * #

Methods

_Wrapped' :: Iso' (C_Module l0) (Unwrapped (C_Module l0)) #

(~) * (C_Module l0) t0 => Rewrapped (C_Module l1) t0 Source # 
type Unwrapped (C_Module l0) Source # 
type Unwrapped (C_Module l0) = (l0, Maybe (ModuleHead l0), [ModulePragma l0], [ImportDecl l0], [Decl l0])

newtype C_XmlPage l Source #

Constructors

C_XmlPage (l, ModuleName l, [ModulePragma l], XName l, [XAttr l], Maybe (Exp l), [Exp l]) 

Instances

Wrapped (C_XmlPage l0) Source # 

Associated Types

type Unwrapped (C_XmlPage l0) :: * #

(~) * (C_XmlPage l0) t0 => Rewrapped (C_XmlPage l1) t0 Source # 
type Unwrapped (C_XmlPage l0) Source # 
type Unwrapped (C_XmlPage l0) = (l0, ModuleName l0, [ModulePragma l0], XName l0, [XAttr l0], Maybe (Exp l0), [Exp l0])

newtype C_XmlHybrid l Source #

Constructors

C_XmlHybrid (l, Maybe (ModuleHead l), [ModulePragma l], [ImportDecl l], [Decl l], XName l, [XAttr l], Maybe (Exp l), [Exp l]) 

Instances

Wrapped (C_XmlHybrid l0) Source # 

Associated Types

type Unwrapped (C_XmlHybrid l0) :: * #

(~) * (C_XmlHybrid l0) t0 => Rewrapped (C_XmlHybrid l1) t0 Source # 
type Unwrapped (C_XmlHybrid l0) Source # 
type Unwrapped (C_XmlHybrid l0) = (l0, Maybe (ModuleHead l0), [ModulePragma l0], [ImportDecl l0], [Decl l0], XName l0, [XAttr l0], Maybe (Exp l0), [Exp l0])

newtype C_DeprText l Source #

Constructors

C_DeprText (l, String) 

Instances

Wrapped (C_DeprText l0) Source # 

Associated Types

type Unwrapped (C_DeprText l0) :: * #

(~) * (C_DeprText l0) t0 => Rewrapped (C_DeprText l1) t0 Source # 
type Unwrapped (C_DeprText l0) Source # 
type Unwrapped (C_DeprText l0) = (l0, String)

newtype C_WarnText l Source #

Constructors

C_WarnText (l, String) 

Instances

Wrapped (C_WarnText l0) Source # 

Associated Types

type Unwrapped (C_WarnText l0) :: * #

(~) * (C_WarnText l0) t0 => Rewrapped (C_WarnText l1) t0 Source # 
type Unwrapped (C_WarnText l0) Source # 
type Unwrapped (C_WarnText l0) = (l0, String)

newtype C_EVar l Source #

Constructors

C_EVar (l, QName l) 

Instances

Wrapped (C_EVar l0) Source # 

Associated Types

type Unwrapped (C_EVar l0) :: * #

Methods

_Wrapped' :: Iso' (C_EVar l0) (Unwrapped (C_EVar l0)) #

(~) * (C_EVar l0) t0 => Rewrapped (C_EVar l1) t0 Source # 
type Unwrapped (C_EVar l0) Source # 
type Unwrapped (C_EVar l0) = (l0, QName l0)

newtype C_EAbs l Source #

Constructors

C_EAbs (l, Namespace l, QName l) 

Instances

Wrapped (C_EAbs l0) Source # 

Associated Types

type Unwrapped (C_EAbs l0) :: * #

Methods

_Wrapped' :: Iso' (C_EAbs l0) (Unwrapped (C_EAbs l0)) #

(~) * (C_EAbs l0) t0 => Rewrapped (C_EAbs l1) t0 Source # 
type Unwrapped (C_EAbs l0) Source # 
type Unwrapped (C_EAbs l0) = (l0, Namespace l0, QName l0)

newtype C_EThingWith l Source #

Constructors

C_EThingWith (l, EWildcard l, QName l, [CName l]) 

Instances

Wrapped (C_EThingWith l0) Source # 

Associated Types

type Unwrapped (C_EThingWith l0) :: * #

(~) * (C_EThingWith l0) t0 => Rewrapped (C_EThingWith l1) t0 Source # 
type Unwrapped (C_EThingWith l0) Source # 
type Unwrapped (C_EThingWith l0) = (l0, EWildcard l0, QName l0, [CName l0])

newtype C_NoWildcard l Source #

Constructors

C_NoWildcard l 

Instances

Wrapped (C_NoWildcard l0) Source # 

Associated Types

type Unwrapped (C_NoWildcard l0) :: * #

(~) * (C_NoWildcard l0) t0 => Rewrapped (C_NoWildcard l1) t0 Source # 
type Unwrapped (C_NoWildcard l0) Source # 
type Unwrapped (C_NoWildcard l0) = l0

newtype C_EWildcard l Source #

Constructors

C_EWildcard (l, Int) 

Instances

Wrapped (C_EWildcard l0) Source # 

Associated Types

type Unwrapped (C_EWildcard l0) :: * #

(~) * (C_EWildcard l0) t0 => Rewrapped (C_EWildcard l1) t0 Source # 
type Unwrapped (C_EWildcard l0) Source # 
type Unwrapped (C_EWildcard l0) = (l0, Int)

newtype C_IVar l Source #

Constructors

C_IVar (l, Name l) 

Instances

Wrapped (C_IVar l0) Source # 

Associated Types

type Unwrapped (C_IVar l0) :: * #

Methods

_Wrapped' :: Iso' (C_IVar l0) (Unwrapped (C_IVar l0)) #

(~) * (C_IVar l0) t0 => Rewrapped (C_IVar l1) t0 Source # 
type Unwrapped (C_IVar l0) Source # 
type Unwrapped (C_IVar l0) = (l0, Name l0)

newtype C_IAbs l Source #

Constructors

C_IAbs (l, Namespace l, Name l) 

Instances

Wrapped (C_IAbs l0) Source # 

Associated Types

type Unwrapped (C_IAbs l0) :: * #

Methods

_Wrapped' :: Iso' (C_IAbs l0) (Unwrapped (C_IAbs l0)) #

(~) * (C_IAbs l0) t0 => Rewrapped (C_IAbs l1) t0 Source # 
type Unwrapped (C_IAbs l0) Source # 
type Unwrapped (C_IAbs l0) = (l0, Namespace l0, Name l0)

newtype C_IThingAll l Source #

Constructors

C_IThingAll (l, Name l) 

Instances

Wrapped (C_IThingAll l0) Source # 

Associated Types

type Unwrapped (C_IThingAll l0) :: * #

(~) * (C_IThingAll l0) t0 => Rewrapped (C_IThingAll l1) t0 Source # 
type Unwrapped (C_IThingAll l0) Source # 
type Unwrapped (C_IThingAll l0) = (l0, Name l0)

newtype C_IThingWith l Source #

Constructors

C_IThingWith (l, Name l, [CName l]) 

Instances

Wrapped (C_IThingWith l0) Source # 

Associated Types

type Unwrapped (C_IThingWith l0) :: * #

(~) * (C_IThingWith l0) t0 => Rewrapped (C_IThingWith l1) t0 Source # 
type Unwrapped (C_IThingWith l0) Source # 
type Unwrapped (C_IThingWith l0) = (l0, Name l0, [CName l0])

newtype C_AssocNone l Source #

Constructors

C_AssocNone l 

Instances

Wrapped (C_AssocNone l0) Source # 

Associated Types

type Unwrapped (C_AssocNone l0) :: * #

(~) * (C_AssocNone l0) t0 => Rewrapped (C_AssocNone l1) t0 Source # 
type Unwrapped (C_AssocNone l0) Source # 
type Unwrapped (C_AssocNone l0) = l0

newtype C_AssocLeft l Source #

Constructors

C_AssocLeft l 

Instances

Wrapped (C_AssocLeft l0) Source # 

Associated Types

type Unwrapped (C_AssocLeft l0) :: * #

(~) * (C_AssocLeft l0) t0 => Rewrapped (C_AssocLeft l1) t0 Source # 
type Unwrapped (C_AssocLeft l0) Source # 
type Unwrapped (C_AssocLeft l0) = l0

newtype C_AssocRight l Source #

Constructors

C_AssocRight l 

Instances

Wrapped (C_AssocRight l0) Source # 

Associated Types

type Unwrapped (C_AssocRight l0) :: * #

(~) * (C_AssocRight l0) t0 => Rewrapped (C_AssocRight l1) t0 Source # 
type Unwrapped (C_AssocRight l0) Source # 
type Unwrapped (C_AssocRight l0) = l0

newtype C_NoNamespace l Source #

Constructors

C_NoNamespace l 

Instances

Wrapped (C_NoNamespace l0) Source # 

Associated Types

type Unwrapped (C_NoNamespace l0) :: * #

(~) * (C_NoNamespace l0) t0 => Rewrapped (C_NoNamespace l1) t0 Source # 
type Unwrapped (C_NoNamespace l0) Source # 
type Unwrapped (C_NoNamespace l0) = l0

newtype C_TypeNamespace l Source #

Constructors

C_TypeNamespace l 

Instances

newtype C_TypeDecl l Source #

Constructors

C_TypeDecl (l, DeclHead l, Type l) 

Instances

Wrapped (C_TypeDecl l0) Source # 

Associated Types

type Unwrapped (C_TypeDecl l0) :: * #

(~) * (C_TypeDecl l0) t0 => Rewrapped (C_TypeDecl l1) t0 Source # 
type Unwrapped (C_TypeDecl l0) Source # 
type Unwrapped (C_TypeDecl l0) = (l0, DeclHead l0, Type l0)

newtype C_TypeFamDecl l Source #

Instances

newtype C_DataDecl l Source #

Constructors

C_DataDecl (l, DataOrNew l, Maybe (Context l), DeclHead l, [QualConDecl l], Maybe (Deriving l)) 

Instances

Wrapped (C_DataDecl l0) Source # 

Associated Types

type Unwrapped (C_DataDecl l0) :: * #

(~) * (C_DataDecl l0) t0 => Rewrapped (C_DataDecl l1) t0 Source # 
type Unwrapped (C_DataDecl l0) Source # 
type Unwrapped (C_DataDecl l0) = (l0, DataOrNew l0, Maybe (Context l0), DeclHead l0, [QualConDecl l0], Maybe (Deriving l0))

newtype C_GDataDecl l Source #

Constructors

C_GDataDecl (l, DataOrNew l, Maybe (Context l), DeclHead l, Maybe (Kind l), [GadtDecl l], Maybe (Deriving l)) 

Instances

Wrapped (C_GDataDecl l0) Source # 

Associated Types

type Unwrapped (C_GDataDecl l0) :: * #

(~) * (C_GDataDecl l0) t0 => Rewrapped (C_GDataDecl l1) t0 Source # 
type Unwrapped (C_GDataDecl l0) Source # 
type Unwrapped (C_GDataDecl l0) = (l0, DataOrNew l0, Maybe (Context l0), DeclHead l0, Maybe (Kind l0), [GadtDecl l0], Maybe (Deriving l0))

newtype C_DataFamDecl l Source #

Constructors

C_DataFamDecl (l, Maybe (Context l), DeclHead l, Maybe (ResultSig l)) 

Instances

Wrapped (C_DataFamDecl l0) Source # 

Associated Types

type Unwrapped (C_DataFamDecl l0) :: * #

(~) * (C_DataFamDecl l0) t0 => Rewrapped (C_DataFamDecl l1) t0 Source # 
type Unwrapped (C_DataFamDecl l0) Source # 
type Unwrapped (C_DataFamDecl l0) = (l0, Maybe (Context l0), DeclHead l0, Maybe (ResultSig l0))

newtype C_TypeInsDecl l Source #

Constructors

C_TypeInsDecl (l, Type l, Type l) 

Instances

Wrapped (C_TypeInsDecl l0) Source # 

Associated Types

type Unwrapped (C_TypeInsDecl l0) :: * #

(~) * (C_TypeInsDecl l0) t0 => Rewrapped (C_TypeInsDecl l1) t0 Source # 
type Unwrapped (C_TypeInsDecl l0) Source # 
type Unwrapped (C_TypeInsDecl l0) = (l0, Type l0, Type l0)

newtype C_DataInsDecl l Source #

Constructors

C_DataInsDecl (l, DataOrNew l, Type l, [QualConDecl l], Maybe (Deriving l)) 

Instances

Wrapped (C_DataInsDecl l0) Source # 

Associated Types

type Unwrapped (C_DataInsDecl l0) :: * #

(~) * (C_DataInsDecl l0) t0 => Rewrapped (C_DataInsDecl l1) t0 Source # 
type Unwrapped (C_DataInsDecl l0) Source # 
type Unwrapped (C_DataInsDecl l0) = (l0, DataOrNew l0, Type l0, [QualConDecl l0], Maybe (Deriving l0))

newtype C_GDataInsDecl l Source #

Constructors

C_GDataInsDecl (l, DataOrNew l, Type l, Maybe (Kind l), [GadtDecl l], Maybe (Deriving l)) 

Instances

Wrapped (C_GDataInsDecl l0) Source # 

Associated Types

type Unwrapped (C_GDataInsDecl l0) :: * #

(~) * (C_GDataInsDecl l0) t0 => Rewrapped (C_GDataInsDecl l1) t0 Source # 
type Unwrapped (C_GDataInsDecl l0) Source # 
type Unwrapped (C_GDataInsDecl l0) = (l0, DataOrNew l0, Type l0, Maybe (Kind l0), [GadtDecl l0], Maybe (Deriving l0))

newtype C_ClassDecl l Source #

Constructors

C_ClassDecl (l, Maybe (Context l), DeclHead l, [FunDep l], Maybe [ClassDecl l]) 

Instances

Wrapped (C_ClassDecl l0) Source # 

Associated Types

type Unwrapped (C_ClassDecl l0) :: * #

(~) * (C_ClassDecl l0) t0 => Rewrapped (C_ClassDecl l1) t0 Source # 
type Unwrapped (C_ClassDecl l0) Source # 
type Unwrapped (C_ClassDecl l0) = (l0, Maybe (Context l0), DeclHead l0, [FunDep l0], Maybe [ClassDecl l0])

newtype C_InstDecl l Source #

Constructors

C_InstDecl (l, Maybe (Overlap l), InstRule l, Maybe [InstDecl l]) 

Instances

Wrapped (C_InstDecl l0) Source # 

Associated Types

type Unwrapped (C_InstDecl l0) :: * #

(~) * (C_InstDecl l0) t0 => Rewrapped (C_InstDecl l1) t0 Source # 
type Unwrapped (C_InstDecl l0) Source # 
type Unwrapped (C_InstDecl l0) = (l0, Maybe (Overlap l0), InstRule l0, Maybe [InstDecl l0])

newtype C_DerivDecl l Source #

Constructors

C_DerivDecl (l, Maybe (Overlap l), InstRule l) 

Instances

Wrapped (C_DerivDecl l0) Source # 

Associated Types

type Unwrapped (C_DerivDecl l0) :: * #

(~) * (C_DerivDecl l0) t0 => Rewrapped (C_DerivDecl l1) t0 Source # 
type Unwrapped (C_DerivDecl l0) Source # 
type Unwrapped (C_DerivDecl l0) = (l0, Maybe (Overlap l0), InstRule l0)

newtype C_InfixDecl l Source #

Constructors

C_InfixDecl (l, Assoc l, Maybe Int, [Op l]) 

Instances

Wrapped (C_InfixDecl l0) Source # 

Associated Types

type Unwrapped (C_InfixDecl l0) :: * #

(~) * (C_InfixDecl l0) t0 => Rewrapped (C_InfixDecl l1) t0 Source # 
type Unwrapped (C_InfixDecl l0) Source # 
type Unwrapped (C_InfixDecl l0) = (l0, Assoc l0, Maybe Int, [Op l0])

newtype C_DefaultDecl l Source #

Constructors

C_DefaultDecl (l, [Type l]) 

Instances

Wrapped (C_DefaultDecl l0) Source # 

Associated Types

type Unwrapped (C_DefaultDecl l0) :: * #

(~) * (C_DefaultDecl l0) t0 => Rewrapped (C_DefaultDecl l1) t0 Source # 
type Unwrapped (C_DefaultDecl l0) Source # 
type Unwrapped (C_DefaultDecl l0) = (l0, [Type l0])

newtype C_SpliceDecl l Source #

Constructors

C_SpliceDecl (l, Exp l) 

Instances

Wrapped (C_SpliceDecl l0) Source # 

Associated Types

type Unwrapped (C_SpliceDecl l0) :: * #

(~) * (C_SpliceDecl l0) t0 => Rewrapped (C_SpliceDecl l1) t0 Source # 
type Unwrapped (C_SpliceDecl l0) Source # 
type Unwrapped (C_SpliceDecl l0) = (l0, Exp l0)

newtype C_TypeSig l Source #

Constructors

C_TypeSig (l, [Name l], Type l) 

Instances

Wrapped (C_TypeSig l0) Source # 

Associated Types

type Unwrapped (C_TypeSig l0) :: * #

(~) * (C_TypeSig l0) t0 => Rewrapped (C_TypeSig l1) t0 Source # 
type Unwrapped (C_TypeSig l0) Source # 
type Unwrapped (C_TypeSig l0) = (l0, [Name l0], Type l0)

newtype C_PatSynSig l Source #

Constructors

C_PatSynSig (l, Name l, Maybe [TyVarBind l], Maybe (Context l), Maybe (Context l), Type l) 

Instances

Wrapped (C_PatSynSig l0) Source # 

Associated Types

type Unwrapped (C_PatSynSig l0) :: * #

(~) * (C_PatSynSig l0) t0 => Rewrapped (C_PatSynSig l1) t0 Source # 
type Unwrapped (C_PatSynSig l0) Source # 
type Unwrapped (C_PatSynSig l0) = (l0, Name l0, Maybe [TyVarBind l0], Maybe (Context l0), Maybe (Context l0), Type l0)

newtype C_FunBind l Source #

Constructors

C_FunBind (l, [Match l]) 

Instances

Wrapped (C_FunBind l0) Source # 

Associated Types

type Unwrapped (C_FunBind l0) :: * #

(~) * (C_FunBind l0) t0 => Rewrapped (C_FunBind l1) t0 Source # 
type Unwrapped (C_FunBind l0) Source # 
type Unwrapped (C_FunBind l0) = (l0, [Match l0])

newtype C_PatBind l Source #

Constructors

C_PatBind (l, Pat l, Rhs l, Maybe (Binds l)) 

Instances

Wrapped (C_PatBind l0) Source # 

Associated Types

type Unwrapped (C_PatBind l0) :: * #

(~) * (C_PatBind l0) t0 => Rewrapped (C_PatBind l1) t0 Source # 
type Unwrapped (C_PatBind l0) Source # 
type Unwrapped (C_PatBind l0) = (l0, Pat l0, Rhs l0, Maybe (Binds l0))

newtype C_PatSyn l Source #

Constructors

C_PatSyn (l, Pat l, Pat l, PatternSynDirection l) 

Instances

Wrapped (C_PatSyn l0) Source # 

Associated Types

type Unwrapped (C_PatSyn l0) :: * #

Methods

_Wrapped' :: Iso' (C_PatSyn l0) (Unwrapped (C_PatSyn l0)) #

(~) * (C_PatSyn l0) t0 => Rewrapped (C_PatSyn l1) t0 Source # 
type Unwrapped (C_PatSyn l0) Source # 
type Unwrapped (C_PatSyn l0) = (l0, Pat l0, Pat l0, PatternSynDirection l0)

newtype C_ForImp l Source #

Constructors

C_ForImp (l, CallConv l, Maybe (Safety l), Maybe String, Name l, Type l) 

Instances

Wrapped (C_ForImp l0) Source # 

Associated Types

type Unwrapped (C_ForImp l0) :: * #

Methods

_Wrapped' :: Iso' (C_ForImp l0) (Unwrapped (C_ForImp l0)) #

(~) * (C_ForImp l0) t0 => Rewrapped (C_ForImp l1) t0 Source # 
type Unwrapped (C_ForImp l0) Source # 
type Unwrapped (C_ForImp l0) = (l0, CallConv l0, Maybe (Safety l0), Maybe String, Name l0, Type l0)

newtype C_ForExp l Source #

Constructors

C_ForExp (l, CallConv l, Maybe String, Name l, Type l) 

Instances

Wrapped (C_ForExp l0) Source # 

Associated Types

type Unwrapped (C_ForExp l0) :: * #

Methods

_Wrapped' :: Iso' (C_ForExp l0) (Unwrapped (C_ForExp l0)) #

(~) * (C_ForExp l0) t0 => Rewrapped (C_ForExp l1) t0 Source # 
type Unwrapped (C_ForExp l0) Source # 
type Unwrapped (C_ForExp l0) = (l0, CallConv l0, Maybe String, Name l0, Type l0)

newtype C_RulePragmaDecl l Source #

Constructors

C_RulePragmaDecl (l, [Rule l]) 

Instances

newtype C_DeprPragmaDecl l Source #

Constructors

C_DeprPragmaDecl (l, [([Name l], String)]) 

Instances

newtype C_WarnPragmaDecl l Source #

Constructors

C_WarnPragmaDecl (l, [([Name l], String)]) 

Instances

newtype C_InlineSig l Source #

Constructors

C_InlineSig (l, Bool, Maybe (Activation l), QName l) 

Instances

Wrapped (C_InlineSig l0) Source # 

Associated Types

type Unwrapped (C_InlineSig l0) :: * #

(~) * (C_InlineSig l0) t0 => Rewrapped (C_InlineSig l1) t0 Source # 
type Unwrapped (C_InlineSig l0) Source # 
type Unwrapped (C_InlineSig l0) = (l0, Bool, Maybe (Activation l0), QName l0)

newtype C_SpecSig l Source #

Constructors

C_SpecSig (l, Maybe (Activation l), QName l, [Type l]) 

Instances

Wrapped (C_SpecSig l0) Source # 

Associated Types

type Unwrapped (C_SpecSig l0) :: * #

(~) * (C_SpecSig l0) t0 => Rewrapped (C_SpecSig l1) t0 Source # 
type Unwrapped (C_SpecSig l0) Source # 
type Unwrapped (C_SpecSig l0) = (l0, Maybe (Activation l0), QName l0, [Type l0])

newtype C_SpecInlineSig l Source #

Constructors

C_SpecInlineSig (l, Bool, Maybe (Activation l), QName l, [Type l]) 

Instances

newtype C_InstSig l Source #

Constructors

C_InstSig (l, InstRule l) 

Instances

Wrapped (C_InstSig l0) Source # 

Associated Types

type Unwrapped (C_InstSig l0) :: * #

(~) * (C_InstSig l0) t0 => Rewrapped (C_InstSig l1) t0 Source # 
type Unwrapped (C_InstSig l0) Source # 
type Unwrapped (C_InstSig l0) = (l0, InstRule l0)

newtype C_AnnPragma l Source #

Constructors

C_AnnPragma (l, Annotation l) 

Instances

Wrapped (C_AnnPragma l0) Source # 

Associated Types

type Unwrapped (C_AnnPragma l0) :: * #

(~) * (C_AnnPragma l0) t0 => Rewrapped (C_AnnPragma l1) t0 Source # 
type Unwrapped (C_AnnPragma l0) Source # 
type Unwrapped (C_AnnPragma l0) = (l0, Annotation l0)

newtype C_MinimalPragma l Source #

Constructors

C_MinimalPragma (l, Maybe (BooleanFormula l)) 

Instances

newtype C_RoleAnnotDecl l Source #

Constructors

C_RoleAnnotDecl (l, QName l, [Role l]) 

Instances

Wrapped (C_RoleAnnotDecl l0) Source # 

Associated Types

type Unwrapped (C_RoleAnnotDecl l0) :: * #

(~) * (C_RoleAnnotDecl l0) t0 => Rewrapped (C_RoleAnnotDecl l1) t0 Source # 
type Unwrapped (C_RoleAnnotDecl l0) Source # 
type Unwrapped (C_RoleAnnotDecl l0) = (l0, QName l0, [Role l0])

newtype C_DHead l Source #

Constructors

C_DHead (l, Name l) 

Instances

Wrapped (C_DHead l0) Source # 

Associated Types

type Unwrapped (C_DHead l0) :: * #

Methods

_Wrapped' :: Iso' (C_DHead l0) (Unwrapped (C_DHead l0)) #

(~) * (C_DHead l0) t0 => Rewrapped (C_DHead l1) t0 Source # 
type Unwrapped (C_DHead l0) Source # 
type Unwrapped (C_DHead l0) = (l0, Name l0)

newtype C_DHInfix l Source #

Constructors

C_DHInfix (l, TyVarBind l, Name l) 

Instances

Wrapped (C_DHInfix l0) Source # 

Associated Types

type Unwrapped (C_DHInfix l0) :: * #

(~) * (C_DHInfix l0) t0 => Rewrapped (C_DHInfix l1) t0 Source # 
type Unwrapped (C_DHInfix l0) Source # 
type Unwrapped (C_DHInfix l0) = (l0, TyVarBind l0, Name l0)

newtype C_DHParen l Source #

Constructors

C_DHParen (l, DeclHead l) 

Instances

Wrapped (C_DHParen l0) Source # 

Associated Types

type Unwrapped (C_DHParen l0) :: * #

(~) * (C_DHParen l0) t0 => Rewrapped (C_DHParen l1) t0 Source # 
type Unwrapped (C_DHParen l0) Source # 
type Unwrapped (C_DHParen l0) = (l0, DeclHead l0)

newtype C_DHApp l Source #

Constructors

C_DHApp (l, DeclHead l, TyVarBind l) 

Instances

Wrapped (C_DHApp l0) Source # 

Associated Types

type Unwrapped (C_DHApp l0) :: * #

Methods

_Wrapped' :: Iso' (C_DHApp l0) (Unwrapped (C_DHApp l0)) #

(~) * (C_DHApp l0) t0 => Rewrapped (C_DHApp l1) t0 Source # 
type Unwrapped (C_DHApp l0) Source # 
type Unwrapped (C_DHApp l0) = (l0, DeclHead l0, TyVarBind l0)

newtype C_IRule l Source #

Constructors

C_IRule (l, Maybe [TyVarBind l], Maybe (Context l), InstHead l) 

Instances

Wrapped (C_IRule l0) Source # 

Associated Types

type Unwrapped (C_IRule l0) :: * #

Methods

_Wrapped' :: Iso' (C_IRule l0) (Unwrapped (C_IRule l0)) #

(~) * (C_IRule l0) t0 => Rewrapped (C_IRule l1) t0 Source # 
type Unwrapped (C_IRule l0) Source # 
type Unwrapped (C_IRule l0) = (l0, Maybe [TyVarBind l0], Maybe (Context l0), InstHead l0)

newtype C_IParen l Source #

Constructors

C_IParen (l, InstRule l) 

Instances

Wrapped (C_IParen l0) Source # 

Associated Types

type Unwrapped (C_IParen l0) :: * #

Methods

_Wrapped' :: Iso' (C_IParen l0) (Unwrapped (C_IParen l0)) #

(~) * (C_IParen l0) t0 => Rewrapped (C_IParen l1) t0 Source # 
type Unwrapped (C_IParen l0) Source # 
type Unwrapped (C_IParen l0) = (l0, InstRule l0)

newtype C_IHCon l Source #

Constructors

C_IHCon (l, QName l) 

Instances

Wrapped (C_IHCon l0) Source # 

Associated Types

type Unwrapped (C_IHCon l0) :: * #

Methods

_Wrapped' :: Iso' (C_IHCon l0) (Unwrapped (C_IHCon l0)) #

(~) * (C_IHCon l0) t0 => Rewrapped (C_IHCon l1) t0 Source # 
type Unwrapped (C_IHCon l0) Source # 
type Unwrapped (C_IHCon l0) = (l0, QName l0)

newtype C_IHInfix l Source #

Constructors

C_IHInfix (l, Type l, QName l) 

Instances

Wrapped (C_IHInfix l0) Source # 

Associated Types

type Unwrapped (C_IHInfix l0) :: * #

(~) * (C_IHInfix l0) t0 => Rewrapped (C_IHInfix l1) t0 Source # 
type Unwrapped (C_IHInfix l0) Source # 
type Unwrapped (C_IHInfix l0) = (l0, Type l0, QName l0)

newtype C_IHParen l Source #

Constructors

C_IHParen (l, InstHead l) 

Instances

Wrapped (C_IHParen l0) Source # 

Associated Types

type Unwrapped (C_IHParen l0) :: * #

(~) * (C_IHParen l0) t0 => Rewrapped (C_IHParen l1) t0 Source # 
type Unwrapped (C_IHParen l0) Source # 
type Unwrapped (C_IHParen l0) = (l0, InstHead l0)

newtype C_IHApp l Source #

Constructors

C_IHApp (l, InstHead l, Type l) 

Instances

Wrapped (C_IHApp l0) Source # 

Associated Types

type Unwrapped (C_IHApp l0) :: * #

Methods

_Wrapped' :: Iso' (C_IHApp l0) (Unwrapped (C_IHApp l0)) #

(~) * (C_IHApp l0) t0 => Rewrapped (C_IHApp l1) t0 Source # 
type Unwrapped (C_IHApp l0) Source # 
type Unwrapped (C_IHApp l0) = (l0, InstHead l0, Type l0)

newtype C_BDecls l Source #

Constructors

C_BDecls (l, [Decl l]) 

Instances

Wrapped (C_BDecls l0) Source # 

Associated Types

type Unwrapped (C_BDecls l0) :: * #

Methods

_Wrapped' :: Iso' (C_BDecls l0) (Unwrapped (C_BDecls l0)) #

(~) * (C_BDecls l0) t0 => Rewrapped (C_BDecls l1) t0 Source # 
type Unwrapped (C_BDecls l0) Source # 
type Unwrapped (C_BDecls l0) = (l0, [Decl l0])

newtype C_IPBinds l Source #

Constructors

C_IPBinds (l, [IPBind l]) 

Instances

Wrapped (C_IPBinds l0) Source # 

Associated Types

type Unwrapped (C_IPBinds l0) :: * #

(~) * (C_IPBinds l0) t0 => Rewrapped (C_IPBinds l1) t0 Source # 
type Unwrapped (C_IPBinds l0) Source # 
type Unwrapped (C_IPBinds l0) = (l0, [IPBind l0])

newtype C_Unidirectional l Source #

Constructors

C_Unidirectional () 

newtype C_KindSig l Source #

Constructors

C_KindSig (l, Kind l) 

Instances

Wrapped (C_KindSig l0) Source # 

Associated Types

type Unwrapped (C_KindSig l0) :: * #

(~) * (C_KindSig l0) t0 => Rewrapped (C_KindSig l1) t0 Source # 
type Unwrapped (C_KindSig l0) Source # 
type Unwrapped (C_KindSig l0) = (l0, Kind l0)

newtype C_TyVarSig l Source #

Constructors

C_TyVarSig (l, TyVarBind l) 

Instances

Wrapped (C_TyVarSig l0) Source # 

Associated Types

type Unwrapped (C_TyVarSig l0) :: * #

(~) * (C_TyVarSig l0) t0 => Rewrapped (C_TyVarSig l1) t0 Source # 
type Unwrapped (C_TyVarSig l0) Source # 
type Unwrapped (C_TyVarSig l0) = (l0, TyVarBind l0)

newtype C_ClsDecl l Source #

Constructors

C_ClsDecl (l, Decl l) 

Instances

Wrapped (C_ClsDecl l0) Source # 

Associated Types

type Unwrapped (C_ClsDecl l0) :: * #

(~) * (C_ClsDecl l0) t0 => Rewrapped (C_ClsDecl l1) t0 Source # 
type Unwrapped (C_ClsDecl l0) Source # 
type Unwrapped (C_ClsDecl l0) = (l0, Decl l0)

newtype C_ClsDataFam l Source #

Constructors

C_ClsDataFam (l, Maybe (Context l), DeclHead l, Maybe (ResultSig l)) 

Instances

Wrapped (C_ClsDataFam l0) Source # 

Associated Types

type Unwrapped (C_ClsDataFam l0) :: * #

(~) * (C_ClsDataFam l0) t0 => Rewrapped (C_ClsDataFam l1) t0 Source # 
type Unwrapped (C_ClsDataFam l0) Source # 
type Unwrapped (C_ClsDataFam l0) = (l0, Maybe (Context l0), DeclHead l0, Maybe (ResultSig l0))

newtype C_ClsTyFam l Source #

Constructors

C_ClsTyFam (l, DeclHead l, Maybe (ResultSig l), Maybe (InjectivityInfo l)) 

Instances

Wrapped (C_ClsTyFam l0) Source # 

Associated Types

type Unwrapped (C_ClsTyFam l0) :: * #

(~) * (C_ClsTyFam l0) t0 => Rewrapped (C_ClsTyFam l1) t0 Source # 
type Unwrapped (C_ClsTyFam l0) Source # 

newtype C_ClsTyDef l Source #

Constructors

C_ClsTyDef (l, TypeEqn l) 

Instances

Wrapped (C_ClsTyDef l0) Source # 

Associated Types

type Unwrapped (C_ClsTyDef l0) :: * #

(~) * (C_ClsTyDef l0) t0 => Rewrapped (C_ClsTyDef l1) t0 Source # 
type Unwrapped (C_ClsTyDef l0) Source # 
type Unwrapped (C_ClsTyDef l0) = (l0, TypeEqn l0)

newtype C_ClsDefSig l Source #

Constructors

C_ClsDefSig (l, Name l, Type l) 

Instances

Wrapped (C_ClsDefSig l0) Source # 

Associated Types

type Unwrapped (C_ClsDefSig l0) :: * #

(~) * (C_ClsDefSig l0) t0 => Rewrapped (C_ClsDefSig l1) t0 Source # 
type Unwrapped (C_ClsDefSig l0) Source # 
type Unwrapped (C_ClsDefSig l0) = (l0, Name l0, Type l0)

newtype C_InsDecl l Source #

Constructors

C_InsDecl (l, Decl l) 

Instances

Wrapped (C_InsDecl l0) Source # 

Associated Types

type Unwrapped (C_InsDecl l0) :: * #

(~) * (C_InsDecl l0) t0 => Rewrapped (C_InsDecl l1) t0 Source # 
type Unwrapped (C_InsDecl l0) Source # 
type Unwrapped (C_InsDecl l0) = (l0, Decl l0)

newtype C_InsType l Source #

Constructors

C_InsType (l, Type l, Type l) 

Instances

Wrapped (C_InsType l0) Source # 

Associated Types

type Unwrapped (C_InsType l0) :: * #

(~) * (C_InsType l0) t0 => Rewrapped (C_InsType l1) t0 Source # 
type Unwrapped (C_InsType l0) Source # 
type Unwrapped (C_InsType l0) = (l0, Type l0, Type l0)

newtype C_InsData l Source #

Constructors

C_InsData (l, DataOrNew l, Type l, [QualConDecl l], Maybe (Deriving l)) 

Instances

Wrapped (C_InsData l0) Source # 

Associated Types

type Unwrapped (C_InsData l0) :: * #

(~) * (C_InsData l0) t0 => Rewrapped (C_InsData l1) t0 Source # 
type Unwrapped (C_InsData l0) Source # 
type Unwrapped (C_InsData l0) = (l0, DataOrNew l0, Type l0, [QualConDecl l0], Maybe (Deriving l0))

newtype C_InsGData l Source #

Constructors

C_InsGData (l, DataOrNew l, Type l, Maybe (Kind l), [GadtDecl l], Maybe (Deriving l)) 

Instances

Wrapped (C_InsGData l0) Source # 

Associated Types

type Unwrapped (C_InsGData l0) :: * #

(~) * (C_InsGData l0) t0 => Rewrapped (C_InsGData l1) t0 Source # 
type Unwrapped (C_InsGData l0) Source # 
type Unwrapped (C_InsGData l0) = (l0, DataOrNew l0, Type l0, Maybe (Kind l0), [GadtDecl l0], Maybe (Deriving l0))

newtype C_DataType l Source #

Constructors

C_DataType l 

Instances

Wrapped (C_DataType l0) Source # 

Associated Types

type Unwrapped (C_DataType l0) :: * #

(~) * (C_DataType l0) t0 => Rewrapped (C_DataType l1) t0 Source # 
type Unwrapped (C_DataType l0) Source # 
type Unwrapped (C_DataType l0) = l0

newtype C_NewType l Source #

Constructors

C_NewType l 

Instances

Wrapped (C_NewType l0) Source # 

Associated Types

type Unwrapped (C_NewType l0) :: * #

(~) * (C_NewType l0) t0 => Rewrapped (C_NewType l1) t0 Source # 
type Unwrapped (C_NewType l0) Source # 
type Unwrapped (C_NewType l0) = l0

newtype C_ConDecl l Source #

Constructors

C_ConDecl (l, Name l, [Type l]) 

Instances

Wrapped (C_ConDecl l0) Source # 

Associated Types

type Unwrapped (C_ConDecl l0) :: * #

(~) * (C_ConDecl l0) t0 => Rewrapped (C_ConDecl l1) t0 Source # 
type Unwrapped (C_ConDecl l0) Source # 
type Unwrapped (C_ConDecl l0) = (l0, Name l0, [Type l0])

newtype C_InfixConDecl l Source #

Constructors

C_InfixConDecl (l, Type l, Name l, Type l) 

Instances

Wrapped (C_InfixConDecl l0) Source # 

Associated Types

type Unwrapped (C_InfixConDecl l0) :: * #

(~) * (C_InfixConDecl l0) t0 => Rewrapped (C_InfixConDecl l1) t0 Source # 
type Unwrapped (C_InfixConDecl l0) Source # 
type Unwrapped (C_InfixConDecl l0) = (l0, Type l0, Name l0, Type l0)

newtype C_RecDecl l Source #

Constructors

C_RecDecl (l, Name l, [FieldDecl l]) 

Instances

Wrapped (C_RecDecl l0) Source # 

Associated Types

type Unwrapped (C_RecDecl l0) :: * #

(~) * (C_RecDecl l0) t0 => Rewrapped (C_RecDecl l1) t0 Source # 
type Unwrapped (C_RecDecl l0) Source # 
type Unwrapped (C_RecDecl l0) = (l0, Name l0, [FieldDecl l0])

newtype C_BangedTy l Source #

Constructors

C_BangedTy l 

Instances

Wrapped (C_BangedTy l0) Source # 

Associated Types

type Unwrapped (C_BangedTy l0) :: * #

(~) * (C_BangedTy l0) t0 => Rewrapped (C_BangedTy l1) t0 Source # 
type Unwrapped (C_BangedTy l0) Source # 
type Unwrapped (C_BangedTy l0) = l0

newtype C_LazyTy l Source #

Constructors

C_LazyTy l 

Instances

Wrapped (C_LazyTy l0) Source # 

Associated Types

type Unwrapped (C_LazyTy l0) :: * #

Methods

_Wrapped' :: Iso' (C_LazyTy l0) (Unwrapped (C_LazyTy l0)) #

(~) * (C_LazyTy l0) t0 => Rewrapped (C_LazyTy l1) t0 Source # 
type Unwrapped (C_LazyTy l0) Source # 
type Unwrapped (C_LazyTy l0) = l0

newtype C_NoStrictAnnot l Source #

Constructors

C_NoStrictAnnot l 

Instances

newtype C_Unpack l Source #

Constructors

C_Unpack l 

Instances

Wrapped (C_Unpack l0) Source # 

Associated Types

type Unwrapped (C_Unpack l0) :: * #

Methods

_Wrapped' :: Iso' (C_Unpack l0) (Unwrapped (C_Unpack l0)) #

(~) * (C_Unpack l0) t0 => Rewrapped (C_Unpack l1) t0 Source # 
type Unwrapped (C_Unpack l0) Source # 
type Unwrapped (C_Unpack l0) = l0

newtype C_NoUnpack l Source #

Constructors

C_NoUnpack l 

Instances

Wrapped (C_NoUnpack l0) Source # 

Associated Types

type Unwrapped (C_NoUnpack l0) :: * #

(~) * (C_NoUnpack l0) t0 => Rewrapped (C_NoUnpack l1) t0 Source # 
type Unwrapped (C_NoUnpack l0) Source # 
type Unwrapped (C_NoUnpack l0) = l0

newtype C_Match l Source #

Constructors

C_Match (l, Name l, [Pat l], Rhs l, Maybe (Binds l)) 

Instances

Wrapped (C_Match l0) Source # 

Associated Types

type Unwrapped (C_Match l0) :: * #

Methods

_Wrapped' :: Iso' (C_Match l0) (Unwrapped (C_Match l0)) #

(~) * (C_Match l0) t0 => Rewrapped (C_Match l1) t0 Source # 
type Unwrapped (C_Match l0) Source # 
type Unwrapped (C_Match l0) = (l0, Name l0, [Pat l0], Rhs l0, Maybe (Binds l0))

newtype C_InfixMatch l Source #

Constructors

C_InfixMatch (l, Pat l, Name l, [Pat l], Rhs l, Maybe (Binds l)) 

Instances

Wrapped (C_InfixMatch l0) Source # 

Associated Types

type Unwrapped (C_InfixMatch l0) :: * #

(~) * (C_InfixMatch l0) t0 => Rewrapped (C_InfixMatch l1) t0 Source # 
type Unwrapped (C_InfixMatch l0) Source # 
type Unwrapped (C_InfixMatch l0) = (l0, Pat l0, Name l0, [Pat l0], Rhs l0, Maybe (Binds l0))

newtype C_UnGuardedRhs l Source #

Constructors

C_UnGuardedRhs (l, Exp l) 

Instances

Wrapped (C_UnGuardedRhs l0) Source # 

Associated Types

type Unwrapped (C_UnGuardedRhs l0) :: * #

(~) * (C_UnGuardedRhs l0) t0 => Rewrapped (C_UnGuardedRhs l1) t0 Source # 
type Unwrapped (C_UnGuardedRhs l0) Source # 
type Unwrapped (C_UnGuardedRhs l0) = (l0, Exp l0)

newtype C_GuardedRhss l Source #

Constructors

C_GuardedRhss (l, [GuardedRhs l]) 

Instances

Wrapped (C_GuardedRhss l0) Source # 

Associated Types

type Unwrapped (C_GuardedRhss l0) :: * #

(~) * (C_GuardedRhss l0) t0 => Rewrapped (C_GuardedRhss l1) t0 Source # 
type Unwrapped (C_GuardedRhss l0) Source # 
type Unwrapped (C_GuardedRhss l0) = (l0, [GuardedRhs l0])

newtype C_CxSingle l Source #

Constructors

C_CxSingle (l, Asst l) 

Instances

Wrapped (C_CxSingle l0) Source # 

Associated Types

type Unwrapped (C_CxSingle l0) :: * #

(~) * (C_CxSingle l0) t0 => Rewrapped (C_CxSingle l1) t0 Source # 
type Unwrapped (C_CxSingle l0) Source # 
type Unwrapped (C_CxSingle l0) = (l0, Asst l0)

newtype C_CxTuple l Source #

Constructors

C_CxTuple (l, [Asst l]) 

Instances

Wrapped (C_CxTuple l0) Source # 

Associated Types

type Unwrapped (C_CxTuple l0) :: * #

(~) * (C_CxTuple l0) t0 => Rewrapped (C_CxTuple l1) t0 Source # 
type Unwrapped (C_CxTuple l0) Source # 
type Unwrapped (C_CxTuple l0) = (l0, [Asst l0])

newtype C_CxEmpty l Source #

Constructors

C_CxEmpty l 

Instances

Wrapped (C_CxEmpty l0) Source # 

Associated Types

type Unwrapped (C_CxEmpty l0) :: * #

(~) * (C_CxEmpty l0) t0 => Rewrapped (C_CxEmpty l1) t0 Source # 
type Unwrapped (C_CxEmpty l0) Source # 
type Unwrapped (C_CxEmpty l0) = l0

newtype C_ClassA l Source #

Constructors

C_ClassA (l, QName l, [Type l]) 

Instances

Wrapped (C_ClassA l0) Source # 

Associated Types

type Unwrapped (C_ClassA l0) :: * #

Methods

_Wrapped' :: Iso' (C_ClassA l0) (Unwrapped (C_ClassA l0)) #

(~) * (C_ClassA l0) t0 => Rewrapped (C_ClassA l1) t0 Source # 
type Unwrapped (C_ClassA l0) Source # 
type Unwrapped (C_ClassA l0) = (l0, QName l0, [Type l0])

newtype C_AppA l Source #

Constructors

C_AppA (l, Name l, [Type l]) 

Instances

Wrapped (C_AppA l0) Source # 

Associated Types

type Unwrapped (C_AppA l0) :: * #

Methods

_Wrapped' :: Iso' (C_AppA l0) (Unwrapped (C_AppA l0)) #

(~) * (C_AppA l0) t0 => Rewrapped (C_AppA l1) t0 Source # 
type Unwrapped (C_AppA l0) Source # 
type Unwrapped (C_AppA l0) = (l0, Name l0, [Type l0])

newtype C_InfixA l Source #

Constructors

C_InfixA (l, Type l, QName l, Type l) 

Instances

Wrapped (C_InfixA l0) Source # 

Associated Types

type Unwrapped (C_InfixA l0) :: * #

Methods

_Wrapped' :: Iso' (C_InfixA l0) (Unwrapped (C_InfixA l0)) #

(~) * (C_InfixA l0) t0 => Rewrapped (C_InfixA l1) t0 Source # 
type Unwrapped (C_InfixA l0) Source # 
type Unwrapped (C_InfixA l0) = (l0, Type l0, QName l0, Type l0)

newtype C_IParam l Source #

Constructors

C_IParam (l, IPName l, Type l) 

Instances

Wrapped (C_IParam l0) Source # 

Associated Types

type Unwrapped (C_IParam l0) :: * #

Methods

_Wrapped' :: Iso' (C_IParam l0) (Unwrapped (C_IParam l0)) #

(~) * (C_IParam l0) t0 => Rewrapped (C_IParam l1) t0 Source # 
type Unwrapped (C_IParam l0) Source # 
type Unwrapped (C_IParam l0) = (l0, IPName l0, Type l0)

newtype C_EqualP l Source #

Constructors

C_EqualP (l, Type l, Type l) 

Instances

Wrapped (C_EqualP l0) Source # 

Associated Types

type Unwrapped (C_EqualP l0) :: * #

Methods

_Wrapped' :: Iso' (C_EqualP l0) (Unwrapped (C_EqualP l0)) #

(~) * (C_EqualP l0) t0 => Rewrapped (C_EqualP l1) t0 Source # 
type Unwrapped (C_EqualP l0) Source # 
type Unwrapped (C_EqualP l0) = (l0, Type l0, Type l0)

newtype C_ParenA l Source #

Constructors

C_ParenA (l, Asst l) 

Instances

Wrapped (C_ParenA l0) Source # 

Associated Types

type Unwrapped (C_ParenA l0) :: * #

Methods

_Wrapped' :: Iso' (C_ParenA l0) (Unwrapped (C_ParenA l0)) #

(~) * (C_ParenA l0) t0 => Rewrapped (C_ParenA l1) t0 Source # 
type Unwrapped (C_ParenA l0) Source # 
type Unwrapped (C_ParenA l0) = (l0, Asst l0)

newtype C_WildCardA l Source #

Constructors

C_WildCardA (l, Maybe (Name l)) 

Instances

Wrapped (C_WildCardA l0) Source # 

Associated Types

type Unwrapped (C_WildCardA l0) :: * #

(~) * (C_WildCardA l0) t0 => Rewrapped (C_WildCardA l1) t0 Source # 
type Unwrapped (C_WildCardA l0) Source # 
type Unwrapped (C_WildCardA l0) = (l0, Maybe (Name l0))

newtype C_TyForall l Source #

Constructors

C_TyForall (l, Maybe [TyVarBind l], Maybe (Context l), Type l) 

Instances

Wrapped (C_TyForall l0) Source # 

Associated Types

type Unwrapped (C_TyForall l0) :: * #

(~) * (C_TyForall l0) t0 => Rewrapped (C_TyForall l1) t0 Source # 
type Unwrapped (C_TyForall l0) Source # 
type Unwrapped (C_TyForall l0) = (l0, Maybe [TyVarBind l0], Maybe (Context l0), Type l0)

newtype C_TyFun l Source #

Constructors

C_TyFun (l, Type l, Type l) 

Instances

Wrapped (C_TyFun l0) Source # 

Associated Types

type Unwrapped (C_TyFun l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyFun l0) (Unwrapped (C_TyFun l0)) #

(~) * (C_TyFun l0) t0 => Rewrapped (C_TyFun l1) t0 Source # 
type Unwrapped (C_TyFun l0) Source # 
type Unwrapped (C_TyFun l0) = (l0, Type l0, Type l0)

newtype C_TyTuple l Source #

Constructors

C_TyTuple (l, Boxed, [Type l]) 

Instances

Wrapped (C_TyTuple l0) Source # 

Associated Types

type Unwrapped (C_TyTuple l0) :: * #

(~) * (C_TyTuple l0) t0 => Rewrapped (C_TyTuple l1) t0 Source # 
type Unwrapped (C_TyTuple l0) Source # 
type Unwrapped (C_TyTuple l0) = (l0, Boxed, [Type l0])

newtype C_TyList l Source #

Constructors

C_TyList (l, Type l) 

Instances

Wrapped (C_TyList l0) Source # 

Associated Types

type Unwrapped (C_TyList l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyList l0) (Unwrapped (C_TyList l0)) #

(~) * (C_TyList l0) t0 => Rewrapped (C_TyList l1) t0 Source # 
type Unwrapped (C_TyList l0) Source # 
type Unwrapped (C_TyList l0) = (l0, Type l0)

newtype C_TyParArray l Source #

Constructors

C_TyParArray (l, Type l) 

Instances

Wrapped (C_TyParArray l0) Source # 

Associated Types

type Unwrapped (C_TyParArray l0) :: * #

(~) * (C_TyParArray l0) t0 => Rewrapped (C_TyParArray l1) t0 Source # 
type Unwrapped (C_TyParArray l0) Source # 
type Unwrapped (C_TyParArray l0) = (l0, Type l0)

newtype C_TyApp l Source #

Constructors

C_TyApp (l, Type l, Type l) 

Instances

Wrapped (C_TyApp l0) Source # 

Associated Types

type Unwrapped (C_TyApp l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyApp l0) (Unwrapped (C_TyApp l0)) #

(~) * (C_TyApp l0) t0 => Rewrapped (C_TyApp l1) t0 Source # 
type Unwrapped (C_TyApp l0) Source # 
type Unwrapped (C_TyApp l0) = (l0, Type l0, Type l0)

newtype C_TyVar l Source #

Constructors

C_TyVar (l, Name l) 

Instances

Wrapped (C_TyVar l0) Source # 

Associated Types

type Unwrapped (C_TyVar l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyVar l0) (Unwrapped (C_TyVar l0)) #

(~) * (C_TyVar l0) t0 => Rewrapped (C_TyVar l1) t0 Source # 
type Unwrapped (C_TyVar l0) Source # 
type Unwrapped (C_TyVar l0) = (l0, Name l0)

newtype C_TyCon l Source #

Constructors

C_TyCon (l, QName l) 

Instances

Wrapped (C_TyCon l0) Source # 

Associated Types

type Unwrapped (C_TyCon l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyCon l0) (Unwrapped (C_TyCon l0)) #

(~) * (C_TyCon l0) t0 => Rewrapped (C_TyCon l1) t0 Source # 
type Unwrapped (C_TyCon l0) Source # 
type Unwrapped (C_TyCon l0) = (l0, QName l0)

newtype C_TyParen l Source #

Constructors

C_TyParen (l, Type l) 

Instances

Wrapped (C_TyParen l0) Source # 

Associated Types

type Unwrapped (C_TyParen l0) :: * #

(~) * (C_TyParen l0) t0 => Rewrapped (C_TyParen l1) t0 Source # 
type Unwrapped (C_TyParen l0) Source # 
type Unwrapped (C_TyParen l0) = (l0, Type l0)

newtype C_TyInfix l Source #

Constructors

C_TyInfix (l, Type l, QName l, Type l) 

Instances

Wrapped (C_TyInfix l0) Source # 

Associated Types

type Unwrapped (C_TyInfix l0) :: * #

(~) * (C_TyInfix l0) t0 => Rewrapped (C_TyInfix l1) t0 Source # 
type Unwrapped (C_TyInfix l0) Source # 
type Unwrapped (C_TyInfix l0) = (l0, Type l0, QName l0, Type l0)

newtype C_TyKind l Source #

Constructors

C_TyKind (l, Type l, Kind l) 

Instances

Wrapped (C_TyKind l0) Source # 

Associated Types

type Unwrapped (C_TyKind l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyKind l0) (Unwrapped (C_TyKind l0)) #

(~) * (C_TyKind l0) t0 => Rewrapped (C_TyKind l1) t0 Source # 
type Unwrapped (C_TyKind l0) Source # 
type Unwrapped (C_TyKind l0) = (l0, Type l0, Kind l0)

newtype C_TyPromoted l Source #

Constructors

C_TyPromoted (l, Promoted l) 

Instances

Wrapped (C_TyPromoted l0) Source # 

Associated Types

type Unwrapped (C_TyPromoted l0) :: * #

(~) * (C_TyPromoted l0) t0 => Rewrapped (C_TyPromoted l1) t0 Source # 
type Unwrapped (C_TyPromoted l0) Source # 
type Unwrapped (C_TyPromoted l0) = (l0, Promoted l0)

newtype C_TyEquals l Source #

Constructors

C_TyEquals (l, Type l, Type l) 

Instances

Wrapped (C_TyEquals l0) Source # 

Associated Types

type Unwrapped (C_TyEquals l0) :: * #

(~) * (C_TyEquals l0) t0 => Rewrapped (C_TyEquals l1) t0 Source # 
type Unwrapped (C_TyEquals l0) Source # 
type Unwrapped (C_TyEquals l0) = (l0, Type l0, Type l0)

newtype C_TySplice l Source #

Constructors

C_TySplice (l, Splice l) 

Instances

Wrapped (C_TySplice l0) Source # 

Associated Types

type Unwrapped (C_TySplice l0) :: * #

(~) * (C_TySplice l0) t0 => Rewrapped (C_TySplice l1) t0 Source # 
type Unwrapped (C_TySplice l0) Source # 
type Unwrapped (C_TySplice l0) = (l0, Splice l0)

newtype C_TyBang l Source #

Constructors

C_TyBang (l, BangType l, Unpackedness l, Type l) 

Instances

Wrapped (C_TyBang l0) Source # 

Associated Types

type Unwrapped (C_TyBang l0) :: * #

Methods

_Wrapped' :: Iso' (C_TyBang l0) (Unwrapped (C_TyBang l0)) #

(~) * (C_TyBang l0) t0 => Rewrapped (C_TyBang l1) t0 Source # 
type Unwrapped (C_TyBang l0) Source # 
type Unwrapped (C_TyBang l0) = (l0, BangType l0, Unpackedness l0, Type l0)

newtype C_TyWildCard l Source #

Constructors

C_TyWildCard (l, Maybe (Name l)) 

Instances

Wrapped (C_TyWildCard l0) Source # 

Associated Types

type Unwrapped (C_TyWildCard l0) :: * #

(~) * (C_TyWildCard l0) t0 => Rewrapped (C_TyWildCard l1) t0 Source # 
type Unwrapped (C_TyWildCard l0) Source # 
type Unwrapped (C_TyWildCard l0) = (l0, Maybe (Name l0))

newtype C_TyQuasiQuote l Source #

Constructors

C_TyQuasiQuote (l, String, String) 

Instances

newtype C_Boxed Source #

Constructors

C_Boxed () 

Instances

newtype C_Unboxed Source #

Constructors

C_Unboxed () 

newtype C_KindStar l Source #

Constructors

C_KindStar l 

Instances

Wrapped (C_KindStar l0) Source # 

Associated Types

type Unwrapped (C_KindStar l0) :: * #

(~) * (C_KindStar l0) t0 => Rewrapped (C_KindStar l1) t0 Source # 
type Unwrapped (C_KindStar l0) Source # 
type Unwrapped (C_KindStar l0) = l0

newtype C_KindFn l Source #

Constructors

C_KindFn (l, Kind l, Kind l) 

Instances

Wrapped (C_KindFn l0) Source # 

Associated Types

type Unwrapped (C_KindFn l0) :: * #

Methods

_Wrapped' :: Iso' (C_KindFn l0) (Unwrapped (C_KindFn l0)) #

(~) * (C_KindFn l0) t0 => Rewrapped (C_KindFn l1) t0 Source # 
type Unwrapped (C_KindFn l0) Source # 
type Unwrapped (C_KindFn l0) = (l0, Kind l0, Kind l0)

newtype C_KindParen l Source #

Constructors

C_KindParen (l, Kind l) 

Instances

Wrapped (C_KindParen l0) Source # 

Associated Types

type Unwrapped (C_KindParen l0) :: * #

(~) * (C_KindParen l0) t0 => Rewrapped (C_KindParen l1) t0 Source # 
type Unwrapped (C_KindParen l0) Source # 
type Unwrapped (C_KindParen l0) = (l0, Kind l0)

newtype C_KindVar l Source #

Constructors

C_KindVar (l, QName l) 

Instances

Wrapped (C_KindVar l0) Source # 

Associated Types

type Unwrapped (C_KindVar l0) :: * #

(~) * (C_KindVar l0) t0 => Rewrapped (C_KindVar l1) t0 Source # 
type Unwrapped (C_KindVar l0) Source # 
type Unwrapped (C_KindVar l0) = (l0, QName l0)

newtype C_KindApp l Source #

Constructors

C_KindApp (l, Kind l, Kind l) 

Instances

Wrapped (C_KindApp l0) Source # 

Associated Types

type Unwrapped (C_KindApp l0) :: * #

(~) * (C_KindApp l0) t0 => Rewrapped (C_KindApp l1) t0 Source # 
type Unwrapped (C_KindApp l0) Source # 
type Unwrapped (C_KindApp l0) = (l0, Kind l0, Kind l0)

newtype C_KindTuple l Source #

Constructors

C_KindTuple (l, [Kind l]) 

Instances

Wrapped (C_KindTuple l0) Source # 

Associated Types

type Unwrapped (C_KindTuple l0) :: * #

(~) * (C_KindTuple l0) t0 => Rewrapped (C_KindTuple l1) t0 Source # 
type Unwrapped (C_KindTuple l0) Source # 
type Unwrapped (C_KindTuple l0) = (l0, [Kind l0])

newtype C_KindList l Source #

Constructors

C_KindList (l, Kind l) 

Instances

Wrapped (C_KindList l0) Source # 

Associated Types

type Unwrapped (C_KindList l0) :: * #

(~) * (C_KindList l0) t0 => Rewrapped (C_KindList l1) t0 Source # 
type Unwrapped (C_KindList l0) Source # 
type Unwrapped (C_KindList l0) = (l0, Kind l0)

newtype C_KindedVar l Source #

Constructors

C_KindedVar (l, Name l, Kind l) 

Instances

Wrapped (C_KindedVar l0) Source # 

Associated Types

type Unwrapped (C_KindedVar l0) :: * #

(~) * (C_KindedVar l0) t0 => Rewrapped (C_KindedVar l1) t0 Source # 
type Unwrapped (C_KindedVar l0) Source # 
type Unwrapped (C_KindedVar l0) = (l0, Name l0, Kind l0)

newtype C_UnkindedVar l Source #

Constructors

C_UnkindedVar (l, Name l) 

Instances

Wrapped (C_UnkindedVar l0) Source # 

Associated Types

type Unwrapped (C_UnkindedVar l0) :: * #

(~) * (C_UnkindedVar l0) t0 => Rewrapped (C_UnkindedVar l1) t0 Source # 
type Unwrapped (C_UnkindedVar l0) Source # 
type Unwrapped (C_UnkindedVar l0) = (l0, Name l0)

newtype C_PromotedCon l Source #

Constructors

C_PromotedCon (l, Bool, QName l) 

Instances

Wrapped (C_PromotedCon l0) Source # 

Associated Types

type Unwrapped (C_PromotedCon l0) :: * #

(~) * (C_PromotedCon l0) t0 => Rewrapped (C_PromotedCon l1) t0 Source # 
type Unwrapped (C_PromotedCon l0) Source # 
type Unwrapped (C_PromotedCon l0) = (l0, Bool, QName l0)

newtype C_PromotedList l Source #

Constructors

C_PromotedList (l, Bool, [Type l]) 

Instances

Wrapped (C_PromotedList l0) Source # 

Associated Types

type Unwrapped (C_PromotedList l0) :: * #

(~) * (C_PromotedList l0) t0 => Rewrapped (C_PromotedList l1) t0 Source # 
type Unwrapped (C_PromotedList l0) Source # 
type Unwrapped (C_PromotedList l0) = (l0, Bool, [Type l0])

newtype C_PromotedTuple l Source #

Constructors

C_PromotedTuple (l, [Type l]) 

Instances

Wrapped (C_PromotedTuple l0) Source # 

Associated Types

type Unwrapped (C_PromotedTuple l0) :: * #

(~) * (C_PromotedTuple l0) t0 => Rewrapped (C_PromotedTuple l1) t0 Source # 
type Unwrapped (C_PromotedTuple l0) Source # 
type Unwrapped (C_PromotedTuple l0) = (l0, [Type l0])

newtype C_PromotedUnit l Source #

Constructors

C_PromotedUnit l 

Instances

newtype C_Var l Source #

Constructors

C_Var (l, QName l) 

Instances

Wrapped (C_Var l0) Source # 

Associated Types

type Unwrapped (C_Var l0) :: * #

Methods

_Wrapped' :: Iso' (C_Var l0) (Unwrapped (C_Var l0)) #

(~) * (C_Var l0) t0 => Rewrapped (C_Var l1) t0 Source # 
type Unwrapped (C_Var l0) Source # 
type Unwrapped (C_Var l0) = (l0, QName l0)

newtype C_IPVar l Source #

Constructors

C_IPVar (l, IPName l) 

Instances

Wrapped (C_IPVar l0) Source # 

Associated Types

type Unwrapped (C_IPVar l0) :: * #

Methods

_Wrapped' :: Iso' (C_IPVar l0) (Unwrapped (C_IPVar l0)) #

(~) * (C_IPVar l0) t0 => Rewrapped (C_IPVar l1) t0 Source # 
type Unwrapped (C_IPVar l0) Source # 
type Unwrapped (C_IPVar l0) = (l0, IPName l0)

newtype C_Con l Source #

Constructors

C_Con (l, QName l) 

Instances

Wrapped (C_Con l0) Source # 

Associated Types

type Unwrapped (C_Con l0) :: * #

Methods

_Wrapped' :: Iso' (C_Con l0) (Unwrapped (C_Con l0)) #

(~) * (C_Con l0) t0 => Rewrapped (C_Con l1) t0 Source # 
type Unwrapped (C_Con l0) Source # 
type Unwrapped (C_Con l0) = (l0, QName l0)

newtype C_Lit l Source #

Constructors

C_Lit (l, Literal l) 

Instances

Wrapped (C_Lit l0) Source # 

Associated Types

type Unwrapped (C_Lit l0) :: * #

Methods

_Wrapped' :: Iso' (C_Lit l0) (Unwrapped (C_Lit l0)) #

(~) * (C_Lit l0) t0 => Rewrapped (C_Lit l1) t0 Source # 
type Unwrapped (C_Lit l0) Source # 
type Unwrapped (C_Lit l0) = (l0, Literal l0)

newtype C_InfixApp l Source #

Constructors

C_InfixApp (l, Exp l, QOp l, Exp l) 

Instances

Wrapped (C_InfixApp l0) Source # 

Associated Types

type Unwrapped (C_InfixApp l0) :: * #

(~) * (C_InfixApp l0) t0 => Rewrapped (C_InfixApp l1) t0 Source # 
type Unwrapped (C_InfixApp l0) Source # 
type Unwrapped (C_InfixApp l0) = (l0, Exp l0, QOp l0, Exp l0)

newtype C_App l Source #

Constructors

C_App (l, Exp l, Exp l) 

Instances

Wrapped (C_App l0) Source # 

Associated Types

type Unwrapped (C_App l0) :: * #

Methods

_Wrapped' :: Iso' (C_App l0) (Unwrapped (C_App l0)) #

(~) * (C_App l0) t0 => Rewrapped (C_App l1) t0 Source # 
type Unwrapped (C_App l0) Source # 
type Unwrapped (C_App l0) = (l0, Exp l0, Exp l0)

newtype C_NegApp l Source #

Constructors

C_NegApp (l, Exp l) 

Instances

Wrapped (C_NegApp l0) Source # 

Associated Types

type Unwrapped (C_NegApp l0) :: * #

Methods

_Wrapped' :: Iso' (C_NegApp l0) (Unwrapped (C_NegApp l0)) #

(~) * (C_NegApp l0) t0 => Rewrapped (C_NegApp l1) t0 Source # 
type Unwrapped (C_NegApp l0) Source # 
type Unwrapped (C_NegApp l0) = (l0, Exp l0)

newtype C_Lambda l Source #

Constructors

C_Lambda (l, [Pat l], Exp l) 

Instances

Wrapped (C_Lambda l0) Source # 

Associated Types

type Unwrapped (C_Lambda l0) :: * #

Methods

_Wrapped' :: Iso' (C_Lambda l0) (Unwrapped (C_Lambda l0)) #

(~) * (C_Lambda l0) t0 => Rewrapped (C_Lambda l1) t0 Source # 
type Unwrapped (C_Lambda l0) Source # 
type Unwrapped (C_Lambda l0) = (l0, [Pat l0], Exp l0)

newtype C_Let l Source #

Constructors

C_Let (l, Binds l, Exp l) 

Instances

Wrapped (C_Let l0) Source # 

Associated Types

type Unwrapped (C_Let l0) :: * #

Methods

_Wrapped' :: Iso' (C_Let l0) (Unwrapped (C_Let l0)) #

(~) * (C_Let l0) t0 => Rewrapped (C_Let l1) t0 Source # 
type Unwrapped (C_Let l0) Source # 
type Unwrapped (C_Let l0) = (l0, Binds l0, Exp l0)

newtype C_If l Source #

Constructors

C_If (l, Exp l, Exp l, Exp l) 

Instances

Wrapped (C_If l0) Source # 

Associated Types

type Unwrapped (C_If l0) :: * #

Methods

_Wrapped' :: Iso' (C_If l0) (Unwrapped (C_If l0)) #

(~) * (C_If l0) t0 => Rewrapped (C_If l1) t0 Source # 
type Unwrapped (C_If l0) Source # 
type Unwrapped (C_If l0) = (l0, Exp l0, Exp l0, Exp l0)

newtype C_MultiIf l Source #

Constructors

C_MultiIf (l, [GuardedRhs l]) 

Instances

Wrapped (C_MultiIf l0) Source # 

Associated Types

type Unwrapped (C_MultiIf l0) :: * #

(~) * (C_MultiIf l0) t0 => Rewrapped (C_MultiIf l1) t0 Source # 
type Unwrapped (C_MultiIf l0) Source # 
type Unwrapped (C_MultiIf l0) = (l0, [GuardedRhs l0])

newtype C_Case l Source #

Constructors

C_Case (l, Exp l, [Alt l]) 

Instances

Wrapped (C_Case l0) Source # 

Associated Types

type Unwrapped (C_Case l0) :: * #

Methods

_Wrapped' :: Iso' (C_Case l0) (Unwrapped (C_Case l0)) #

(~) * (C_Case l0) t0 => Rewrapped (C_Case l1) t0 Source # 
type Unwrapped (C_Case l0) Source # 
type Unwrapped (C_Case l0) = (l0, Exp l0, [Alt l0])

newtype C_Do l Source #

Constructors

C_Do (l, [Stmt l]) 

Instances

Wrapped (C_Do l0) Source # 

Associated Types

type Unwrapped (C_Do l0) :: * #

Methods

_Wrapped' :: Iso' (C_Do l0) (Unwrapped (C_Do l0)) #

(~) * (C_Do l0) t0 => Rewrapped (C_Do l1) t0 Source # 
type Unwrapped (C_Do l0) Source # 
type Unwrapped (C_Do l0) = (l0, [Stmt l0])

newtype C_MDo l Source #

Constructors

C_MDo (l, [Stmt l]) 

Instances

Wrapped (C_MDo l0) Source # 

Associated Types

type Unwrapped (C_MDo l0) :: * #

Methods

_Wrapped' :: Iso' (C_MDo l0) (Unwrapped (C_MDo l0)) #

(~) * (C_MDo l0) t0 => Rewrapped (C_MDo l1) t0 Source # 
type Unwrapped (C_MDo l0) Source # 
type Unwrapped (C_MDo l0) = (l0, [Stmt l0])

newtype C_Tuple l Source #

Constructors

C_Tuple (l, Boxed, [Exp l]) 

Instances

Wrapped (C_Tuple l0) Source # 

Associated Types

type Unwrapped (C_Tuple l0) :: * #

Methods

_Wrapped' :: Iso' (C_Tuple l0) (Unwrapped (C_Tuple l0)) #

(~) * (C_Tuple l0) t0 => Rewrapped (C_Tuple l1) t0 Source # 
type Unwrapped (C_Tuple l0) Source # 
type Unwrapped (C_Tuple l0) = (l0, Boxed, [Exp l0])

newtype C_TupleSection l Source #

Constructors

C_TupleSection (l, Boxed, [Maybe (Exp l)]) 

Instances

Wrapped (C_TupleSection l0) Source # 

Associated Types

type Unwrapped (C_TupleSection l0) :: * #

(~) * (C_TupleSection l0) t0 => Rewrapped (C_TupleSection l1) t0 Source # 
type Unwrapped (C_TupleSection l0) Source # 
type Unwrapped (C_TupleSection l0) = (l0, Boxed, [Maybe (Exp l0)])

newtype C_List l Source #

Constructors

C_List (l, [Exp l]) 

Instances

Wrapped (C_List l0) Source # 

Associated Types

type Unwrapped (C_List l0) :: * #

Methods

_Wrapped' :: Iso' (C_List l0) (Unwrapped (C_List l0)) #

(~) * (C_List l0) t0 => Rewrapped (C_List l1) t0 Source # 
type Unwrapped (C_List l0) Source # 
type Unwrapped (C_List l0) = (l0, [Exp l0])

newtype C_ParArray l Source #

Constructors

C_ParArray (l, [Exp l]) 

Instances

Wrapped (C_ParArray l0) Source # 

Associated Types

type Unwrapped (C_ParArray l0) :: * #

(~) * (C_ParArray l0) t0 => Rewrapped (C_ParArray l1) t0 Source # 
type Unwrapped (C_ParArray l0) Source # 
type Unwrapped (C_ParArray l0) = (l0, [Exp l0])

newtype C_Paren l Source #

Constructors

C_Paren (l, Exp l) 

Instances

Wrapped (C_Paren l0) Source # 

Associated Types

type Unwrapped (C_Paren l0) :: * #

Methods

_Wrapped' :: Iso' (C_Paren l0) (Unwrapped (C_Paren l0)) #

(~) * (C_Paren l0) t0 => Rewrapped (C_Paren l1) t0 Source # 
type Unwrapped (C_Paren l0) Source # 
type Unwrapped (C_Paren l0) = (l0, Exp l0)

newtype C_LeftSection l Source #

Constructors

C_LeftSection (l, Exp l, QOp l) 

Instances

Wrapped (C_LeftSection l0) Source # 

Associated Types

type Unwrapped (C_LeftSection l0) :: * #

(~) * (C_LeftSection l0) t0 => Rewrapped (C_LeftSection l1) t0 Source # 
type Unwrapped (C_LeftSection l0) Source # 
type Unwrapped (C_LeftSection l0) = (l0, Exp l0, QOp l0)

newtype C_RightSection l Source #

Constructors

C_RightSection (l, QOp l, Exp l) 

Instances

Wrapped (C_RightSection l0) Source # 

Associated Types

type Unwrapped (C_RightSection l0) :: * #

(~) * (C_RightSection l0) t0 => Rewrapped (C_RightSection l1) t0 Source # 
type Unwrapped (C_RightSection l0) Source # 
type Unwrapped (C_RightSection l0) = (l0, QOp l0, Exp l0)

newtype C_RecConstr l Source #

Constructors

C_RecConstr (l, QName l, [FieldUpdate l]) 

Instances

Wrapped (C_RecConstr l0) Source # 

Associated Types

type Unwrapped (C_RecConstr l0) :: * #

(~) * (C_RecConstr l0) t0 => Rewrapped (C_RecConstr l1) t0 Source # 
type Unwrapped (C_RecConstr l0) Source # 
type Unwrapped (C_RecConstr l0) = (l0, QName l0, [FieldUpdate l0])

newtype C_RecUpdate l Source #

Constructors

C_RecUpdate (l, Exp l, [FieldUpdate l]) 

Instances

Wrapped (C_RecUpdate l0) Source # 

Associated Types

type Unwrapped (C_RecUpdate l0) :: * #

(~) * (C_RecUpdate l0) t0 => Rewrapped (C_RecUpdate l1) t0 Source # 
type Unwrapped (C_RecUpdate l0) Source # 
type Unwrapped (C_RecUpdate l0) = (l0, Exp l0, [FieldUpdate l0])

newtype C_EnumFrom l Source #

Constructors

C_EnumFrom (l, Exp l) 

Instances

Wrapped (C_EnumFrom l0) Source # 

Associated Types

type Unwrapped (C_EnumFrom l0) :: * #

(~) * (C_EnumFrom l0) t0 => Rewrapped (C_EnumFrom l1) t0 Source # 
type Unwrapped (C_EnumFrom l0) Source # 
type Unwrapped (C_EnumFrom l0) = (l0, Exp l0)

newtype C_EnumFromTo l Source #

Constructors

C_EnumFromTo (l, Exp l, Exp l) 

Instances

Wrapped (C_EnumFromTo l0) Source # 

Associated Types

type Unwrapped (C_EnumFromTo l0) :: * #

(~) * (C_EnumFromTo l0) t0 => Rewrapped (C_EnumFromTo l1) t0 Source # 
type Unwrapped (C_EnumFromTo l0) Source # 
type Unwrapped (C_EnumFromTo l0) = (l0, Exp l0, Exp l0)

newtype C_EnumFromThen l Source #

Constructors

C_EnumFromThen (l, Exp l, Exp l) 

Instances

Wrapped (C_EnumFromThen l0) Source # 

Associated Types

type Unwrapped (C_EnumFromThen l0) :: * #

(~) * (C_EnumFromThen l0) t0 => Rewrapped (C_EnumFromThen l1) t0 Source # 
type Unwrapped (C_EnumFromThen l0) Source # 
type Unwrapped (C_EnumFromThen l0) = (l0, Exp l0, Exp l0)

newtype C_EnumFromThenTo l Source #

Constructors

C_EnumFromThenTo (l, Exp l, Exp l, Exp l) 

Instances

newtype C_ParArrayFromTo l Source #

Constructors

C_ParArrayFromTo (l, Exp l, Exp l) 

Instances

newtype C_ListComp l Source #

Constructors

C_ListComp (l, Exp l, [QualStmt l]) 

Instances

Wrapped (C_ListComp l0) Source # 

Associated Types

type Unwrapped (C_ListComp l0) :: * #

(~) * (C_ListComp l0) t0 => Rewrapped (C_ListComp l1) t0 Source # 
type Unwrapped (C_ListComp l0) Source # 
type Unwrapped (C_ListComp l0) = (l0, Exp l0, [QualStmt l0])

newtype C_ParComp l Source #

Constructors

C_ParComp (l, Exp l, [[QualStmt l]]) 

Instances

Wrapped (C_ParComp l0) Source # 

Associated Types

type Unwrapped (C_ParComp l0) :: * #

(~) * (C_ParComp l0) t0 => Rewrapped (C_ParComp l1) t0 Source # 
type Unwrapped (C_ParComp l0) Source # 
type Unwrapped (C_ParComp l0) = (l0, Exp l0, [[QualStmt l0]])

newtype C_ParArrayComp l Source #

Constructors

C_ParArrayComp (l, Exp l, [[QualStmt l]]) 

Instances

Wrapped (C_ParArrayComp l0) Source # 

Associated Types

type Unwrapped (C_ParArrayComp l0) :: * #

(~) * (C_ParArrayComp l0) t0 => Rewrapped (C_ParArrayComp l1) t0 Source # 
type Unwrapped (C_ParArrayComp l0) Source # 
type Unwrapped (C_ParArrayComp l0) = (l0, Exp l0, [[QualStmt l0]])

newtype C_ExpTypeSig l Source #

Constructors

C_ExpTypeSig (l, Exp l, Type l) 

Instances

Wrapped (C_ExpTypeSig l0) Source # 

Associated Types

type Unwrapped (C_ExpTypeSig l0) :: * #

(~) * (C_ExpTypeSig l0) t0 => Rewrapped (C_ExpTypeSig l1) t0 Source # 
type Unwrapped (C_ExpTypeSig l0) Source # 
type Unwrapped (C_ExpTypeSig l0) = (l0, Exp l0, Type l0)

newtype C_VarQuote l Source #

Constructors

C_VarQuote (l, QName l) 

Instances

Wrapped (C_VarQuote l0) Source # 

Associated Types

type Unwrapped (C_VarQuote l0) :: * #

(~) * (C_VarQuote l0) t0 => Rewrapped (C_VarQuote l1) t0 Source # 
type Unwrapped (C_VarQuote l0) Source # 
type Unwrapped (C_VarQuote l0) = (l0, QName l0)

newtype C_TypQuote l Source #

Constructors

C_TypQuote (l, QName l) 

Instances

Wrapped (C_TypQuote l0) Source # 

Associated Types

type Unwrapped (C_TypQuote l0) :: * #

(~) * (C_TypQuote l0) t0 => Rewrapped (C_TypQuote l1) t0 Source # 
type Unwrapped (C_TypQuote l0) Source # 
type Unwrapped (C_TypQuote l0) = (l0, QName l0)

newtype C_BracketExp l Source #

Constructors

C_BracketExp (l, Bracket l) 

Instances

Wrapped (C_BracketExp l0) Source # 

Associated Types

type Unwrapped (C_BracketExp l0) :: * #

(~) * (C_BracketExp l0) t0 => Rewrapped (C_BracketExp l1) t0 Source # 
type Unwrapped (C_BracketExp l0) Source # 
type Unwrapped (C_BracketExp l0) = (l0, Bracket l0)

newtype C_SpliceExp l Source #

Constructors

C_SpliceExp (l, Splice l) 

Instances

Wrapped (C_SpliceExp l0) Source # 

Associated Types

type Unwrapped (C_SpliceExp l0) :: * #

(~) * (C_SpliceExp l0) t0 => Rewrapped (C_SpliceExp l1) t0 Source # 
type Unwrapped (C_SpliceExp l0) Source # 
type Unwrapped (C_SpliceExp l0) = (l0, Splice l0)

newtype C_QuasiQuote l Source #

Constructors

C_QuasiQuote (l, String, String) 

Instances

Wrapped (C_QuasiQuote l0) Source # 

Associated Types

type Unwrapped (C_QuasiQuote l0) :: * #

(~) * (C_QuasiQuote l0) t0 => Rewrapped (C_QuasiQuote l1) t0 Source # 
type Unwrapped (C_QuasiQuote l0) Source # 
type Unwrapped (C_QuasiQuote l0) = (l0, String, String)

newtype C_TypeApp l Source #

Constructors

C_TypeApp (l, Type l) 

Instances

Wrapped (C_TypeApp l0) Source # 

Associated Types

type Unwrapped (C_TypeApp l0) :: * #

(~) * (C_TypeApp l0) t0 => Rewrapped (C_TypeApp l1) t0 Source # 
type Unwrapped (C_TypeApp l0) Source # 
type Unwrapped (C_TypeApp l0) = (l0, Type l0)

newtype C_XTag l Source #

Constructors

C_XTag (l, XName l, [XAttr l], Maybe (Exp l), [Exp l]) 

Instances

Wrapped (C_XTag l0) Source # 

Associated Types

type Unwrapped (C_XTag l0) :: * #

Methods

_Wrapped' :: Iso' (C_XTag l0) (Unwrapped (C_XTag l0)) #

(~) * (C_XTag l0) t0 => Rewrapped (C_XTag l1) t0 Source # 
type Unwrapped (C_XTag l0) Source # 
type Unwrapped (C_XTag l0) = (l0, XName l0, [XAttr l0], Maybe (Exp l0), [Exp l0])

newtype C_XETag l Source #

Constructors

C_XETag (l, XName l, [XAttr l], Maybe (Exp l)) 

Instances

Wrapped (C_XETag l0) Source # 

Associated Types

type Unwrapped (C_XETag l0) :: * #

Methods

_Wrapped' :: Iso' (C_XETag l0) (Unwrapped (C_XETag l0)) #

(~) * (C_XETag l0) t0 => Rewrapped (C_XETag l1) t0 Source # 
type Unwrapped (C_XETag l0) Source # 
type Unwrapped (C_XETag l0) = (l0, XName l0, [XAttr l0], Maybe (Exp l0))

newtype C_XPcdata l Source #

Constructors

C_XPcdata (l, String) 

Instances

Wrapped (C_XPcdata l0) Source # 

Associated Types

type Unwrapped (C_XPcdata l0) :: * #

(~) * (C_XPcdata l0) t0 => Rewrapped (C_XPcdata l1) t0 Source # 
type Unwrapped (C_XPcdata l0) Source # 
type Unwrapped (C_XPcdata l0) = (l0, String)

newtype C_XExpTag l Source #

Constructors

C_XExpTag (l, Exp l) 

Instances

Wrapped (C_XExpTag l0) Source # 

Associated Types

type Unwrapped (C_XExpTag l0) :: * #

(~) * (C_XExpTag l0) t0 => Rewrapped (C_XExpTag l1) t0 Source # 
type Unwrapped (C_XExpTag l0) Source # 
type Unwrapped (C_XExpTag l0) = (l0, Exp l0)

newtype C_XChildTag l Source #

Constructors

C_XChildTag (l, [Exp l]) 

Instances

Wrapped (C_XChildTag l0) Source # 

Associated Types

type Unwrapped (C_XChildTag l0) :: * #

(~) * (C_XChildTag l0) t0 => Rewrapped (C_XChildTag l1) t0 Source # 
type Unwrapped (C_XChildTag l0) Source # 
type Unwrapped (C_XChildTag l0) = (l0, [Exp l0])

newtype C_CorePragma l Source #

Constructors

C_CorePragma (l, String, Exp l) 

Instances

Wrapped (C_CorePragma l0) Source # 

Associated Types

type Unwrapped (C_CorePragma l0) :: * #

(~) * (C_CorePragma l0) t0 => Rewrapped (C_CorePragma l1) t0 Source # 
type Unwrapped (C_CorePragma l0) Source # 
type Unwrapped (C_CorePragma l0) = (l0, String, Exp l0)

newtype C_SCCPragma l Source #

Constructors

C_SCCPragma (l, String, Exp l) 

Instances

Wrapped (C_SCCPragma l0) Source # 

Associated Types

type Unwrapped (C_SCCPragma l0) :: * #

(~) * (C_SCCPragma l0) t0 => Rewrapped (C_SCCPragma l1) t0 Source # 
type Unwrapped (C_SCCPragma l0) Source # 
type Unwrapped (C_SCCPragma l0) = (l0, String, Exp l0)

newtype C_GenPragma l Source #

Constructors

C_GenPragma (l, String, (Int, Int), (Int, Int), Exp l) 

Instances

Wrapped (C_GenPragma l0) Source # 

Associated Types

type Unwrapped (C_GenPragma l0) :: * #

(~) * (C_GenPragma l0) t0 => Rewrapped (C_GenPragma l1) t0 Source # 
type Unwrapped (C_GenPragma l0) Source # 
type Unwrapped (C_GenPragma l0) = (l0, String, (Int, Int), (Int, Int), Exp l0)

newtype C_Proc l Source #

Constructors

C_Proc (l, Pat l, Exp l) 

Instances

Wrapped (C_Proc l0) Source # 

Associated Types

type Unwrapped (C_Proc l0) :: * #

Methods

_Wrapped' :: Iso' (C_Proc l0) (Unwrapped (C_Proc l0)) #

(~) * (C_Proc l0) t0 => Rewrapped (C_Proc l1) t0 Source # 
type Unwrapped (C_Proc l0) Source # 
type Unwrapped (C_Proc l0) = (l0, Pat l0, Exp l0)

newtype C_LeftArrApp l Source #

Constructors

C_LeftArrApp (l, Exp l, Exp l) 

Instances

Wrapped (C_LeftArrApp l0) Source # 

Associated Types

type Unwrapped (C_LeftArrApp l0) :: * #

(~) * (C_LeftArrApp l0) t0 => Rewrapped (C_LeftArrApp l1) t0 Source # 
type Unwrapped (C_LeftArrApp l0) Source # 
type Unwrapped (C_LeftArrApp l0) = (l0, Exp l0, Exp l0)

newtype C_RightArrApp l Source #

Constructors

C_RightArrApp (l, Exp l, Exp l) 

Instances

Wrapped (C_RightArrApp l0) Source # 

Associated Types

type Unwrapped (C_RightArrApp l0) :: * #

(~) * (C_RightArrApp l0) t0 => Rewrapped (C_RightArrApp l1) t0 Source # 
type Unwrapped (C_RightArrApp l0) Source # 
type Unwrapped (C_RightArrApp l0) = (l0, Exp l0, Exp l0)

newtype C_LeftArrHighApp l Source #

Constructors

C_LeftArrHighApp (l, Exp l, Exp l) 

Instances

newtype C_RightArrHighApp l Source #

Constructors

C_RightArrHighApp (l, Exp l, Exp l) 

Instances

newtype C_LCase l Source #

Constructors

C_LCase (l, [Alt l]) 

Instances

Wrapped (C_LCase l0) Source # 

Associated Types

type Unwrapped (C_LCase l0) :: * #

Methods

_Wrapped' :: Iso' (C_LCase l0) (Unwrapped (C_LCase l0)) #

(~) * (C_LCase l0) t0 => Rewrapped (C_LCase l1) t0 Source # 
type Unwrapped (C_LCase l0) Source # 
type Unwrapped (C_LCase l0) = (l0, [Alt l0])

newtype C_ExprHole l Source #

Constructors

C_ExprHole l 

Instances

Wrapped (C_ExprHole l0) Source # 

Associated Types

type Unwrapped (C_ExprHole l0) :: * #

(~) * (C_ExprHole l0) t0 => Rewrapped (C_ExprHole l1) t0 Source # 
type Unwrapped (C_ExprHole l0) Source # 
type Unwrapped (C_ExprHole l0) = l0

newtype C_Generator l Source #

Constructors

C_Generator (l, Pat l, Exp l) 

Instances

Wrapped (C_Generator l0) Source # 

Associated Types

type Unwrapped (C_Generator l0) :: * #

(~) * (C_Generator l0) t0 => Rewrapped (C_Generator l1) t0 Source # 
type Unwrapped (C_Generator l0) Source # 
type Unwrapped (C_Generator l0) = (l0, Pat l0, Exp l0)

newtype C_Qualifier l Source #

Constructors

C_Qualifier (l, Exp l) 

Instances

Wrapped (C_Qualifier l0) Source # 

Associated Types

type Unwrapped (C_Qualifier l0) :: * #

(~) * (C_Qualifier l0) t0 => Rewrapped (C_Qualifier l1) t0 Source # 
type Unwrapped (C_Qualifier l0) Source # 
type Unwrapped (C_Qualifier l0) = (l0, Exp l0)

newtype C_LetStmt l Source #

Constructors

C_LetStmt (l, Binds l) 

Instances

Wrapped (C_LetStmt l0) Source # 

Associated Types

type Unwrapped (C_LetStmt l0) :: * #

(~) * (C_LetStmt l0) t0 => Rewrapped (C_LetStmt l1) t0 Source # 
type Unwrapped (C_LetStmt l0) Source # 
type Unwrapped (C_LetStmt l0) = (l0, Binds l0)

newtype C_RecStmt l Source #

Constructors

C_RecStmt (l, [Stmt l]) 

Instances

Wrapped (C_RecStmt l0) Source # 

Associated Types

type Unwrapped (C_RecStmt l0) :: * #

(~) * (C_RecStmt l0) t0 => Rewrapped (C_RecStmt l1) t0 Source # 
type Unwrapped (C_RecStmt l0) Source # 
type Unwrapped (C_RecStmt l0) = (l0, [Stmt l0])

newtype C_QualStmt l Source #

Constructors

C_QualStmt (l, Stmt l) 

Instances

Wrapped (C_QualStmt l0) Source # 

Associated Types

type Unwrapped (C_QualStmt l0) :: * #

(~) * (C_QualStmt l0) t0 => Rewrapped (C_QualStmt l1) t0 Source # 
type Unwrapped (C_QualStmt l0) Source # 
type Unwrapped (C_QualStmt l0) = (l0, Stmt l0)

newtype C_ThenTrans l Source #

Constructors

C_ThenTrans (l, Exp l) 

Instances

Wrapped (C_ThenTrans l0) Source # 

Associated Types

type Unwrapped (C_ThenTrans l0) :: * #

(~) * (C_ThenTrans l0) t0 => Rewrapped (C_ThenTrans l1) t0 Source # 
type Unwrapped (C_ThenTrans l0) Source # 
type Unwrapped (C_ThenTrans l0) = (l0, Exp l0)

newtype C_ThenBy l Source #

Constructors

C_ThenBy (l, Exp l, Exp l) 

Instances

Wrapped (C_ThenBy l0) Source # 

Associated Types

type Unwrapped (C_ThenBy l0) :: * #

Methods

_Wrapped' :: Iso' (C_ThenBy l0) (Unwrapped (C_ThenBy l0)) #

(~) * (C_ThenBy l0) t0 => Rewrapped (C_ThenBy l1) t0 Source # 
type Unwrapped (C_ThenBy l0) Source # 
type Unwrapped (C_ThenBy l0) = (l0, Exp l0, Exp l0)

newtype C_GroupBy l Source #

Constructors

C_GroupBy (l, Exp l) 

Instances

Wrapped (C_GroupBy l0) Source # 

Associated Types

type Unwrapped (C_GroupBy l0) :: * #

(~) * (C_GroupBy l0) t0 => Rewrapped (C_GroupBy l1) t0 Source # 
type Unwrapped (C_GroupBy l0) Source # 
type Unwrapped (C_GroupBy l0) = (l0, Exp l0)

newtype C_GroupUsing l Source #

Constructors

C_GroupUsing (l, Exp l) 

Instances

Wrapped (C_GroupUsing l0) Source # 

Associated Types

type Unwrapped (C_GroupUsing l0) :: * #

(~) * (C_GroupUsing l0) t0 => Rewrapped (C_GroupUsing l1) t0 Source # 
type Unwrapped (C_GroupUsing l0) Source # 
type Unwrapped (C_GroupUsing l0) = (l0, Exp l0)

newtype C_GroupByUsing l Source #

Constructors

C_GroupByUsing (l, Exp l, Exp l) 

Instances

Wrapped (C_GroupByUsing l0) Source # 

Associated Types

type Unwrapped (C_GroupByUsing l0) :: * #

(~) * (C_GroupByUsing l0) t0 => Rewrapped (C_GroupByUsing l1) t0 Source # 
type Unwrapped (C_GroupByUsing l0) Source # 
type Unwrapped (C_GroupByUsing l0) = (l0, Exp l0, Exp l0)

newtype C_FieldUpdate l Source #

Constructors

C_FieldUpdate (l, QName l, Exp l) 

Instances

Wrapped (C_FieldUpdate l0) Source # 

Associated Types

type Unwrapped (C_FieldUpdate l0) :: * #

(~) * (C_FieldUpdate l0) t0 => Rewrapped (C_FieldUpdate l1) t0 Source # 
type Unwrapped (C_FieldUpdate l0) Source # 
type Unwrapped (C_FieldUpdate l0) = (l0, QName l0, Exp l0)

newtype C_FieldPun l Source #

Constructors

C_FieldPun (l, QName l) 

Instances

Wrapped (C_FieldPun l0) Source # 

Associated Types

type Unwrapped (C_FieldPun l0) :: * #

(~) * (C_FieldPun l0) t0 => Rewrapped (C_FieldPun l1) t0 Source # 
type Unwrapped (C_FieldPun l0) Source # 
type Unwrapped (C_FieldPun l0) = (l0, QName l0)

newtype C_FieldWildcard l Source #

Constructors

C_FieldWildcard l 

Instances

newtype C_PVar l Source #

Constructors

C_PVar (l, Name l) 

Instances

Wrapped (C_PVar l0) Source # 

Associated Types

type Unwrapped (C_PVar l0) :: * #

Methods

_Wrapped' :: Iso' (C_PVar l0) (Unwrapped (C_PVar l0)) #

(~) * (C_PVar l0) t0 => Rewrapped (C_PVar l1) t0 Source # 
type Unwrapped (C_PVar l0) Source # 
type Unwrapped (C_PVar l0) = (l0, Name l0)

newtype C_PLit l Source #

Constructors

C_PLit (l, Sign l, Literal l) 

Instances

Wrapped (C_PLit l0) Source # 

Associated Types

type Unwrapped (C_PLit l0) :: * #

Methods

_Wrapped' :: Iso' (C_PLit l0) (Unwrapped (C_PLit l0)) #

(~) * (C_PLit l0) t0 => Rewrapped (C_PLit l1) t0 Source # 
type Unwrapped (C_PLit l0) Source # 
type Unwrapped (C_PLit l0) = (l0, Sign l0, Literal l0)

newtype C_PNPlusK l Source #

Constructors

C_PNPlusK (l, Name l, Integer) 

Instances

Wrapped (C_PNPlusK l0) Source # 

Associated Types

type Unwrapped (C_PNPlusK l0) :: * #

(~) * (C_PNPlusK l0) t0 => Rewrapped (C_PNPlusK l1) t0 Source # 
type Unwrapped (C_PNPlusK l0) Source # 
type Unwrapped (C_PNPlusK l0) = (l0, Name l0, Integer)

newtype C_PInfixApp l Source #

Constructors

C_PInfixApp (l, Pat l, QName l, Pat l) 

Instances

Wrapped (C_PInfixApp l0) Source # 

Associated Types

type Unwrapped (C_PInfixApp l0) :: * #

(~) * (C_PInfixApp l0) t0 => Rewrapped (C_PInfixApp l1) t0 Source # 
type Unwrapped (C_PInfixApp l0) Source # 
type Unwrapped (C_PInfixApp l0) = (l0, Pat l0, QName l0, Pat l0)

newtype C_PApp l Source #

Constructors

C_PApp (l, QName l, [Pat l]) 

Instances

Wrapped (C_PApp l0) Source # 

Associated Types

type Unwrapped (C_PApp l0) :: * #

Methods

_Wrapped' :: Iso' (C_PApp l0) (Unwrapped (C_PApp l0)) #

(~) * (C_PApp l0) t0 => Rewrapped (C_PApp l1) t0 Source # 
type Unwrapped (C_PApp l0) Source # 
type Unwrapped (C_PApp l0) = (l0, QName l0, [Pat l0])

newtype C_PTuple l Source #

Constructors

C_PTuple (l, Boxed, [Pat l]) 

Instances

Wrapped (C_PTuple l0) Source # 

Associated Types

type Unwrapped (C_PTuple l0) :: * #

Methods

_Wrapped' :: Iso' (C_PTuple l0) (Unwrapped (C_PTuple l0)) #

(~) * (C_PTuple l0) t0 => Rewrapped (C_PTuple l1) t0 Source # 
type Unwrapped (C_PTuple l0) Source # 
type Unwrapped (C_PTuple l0) = (l0, Boxed, [Pat l0])

newtype C_PList l Source #

Constructors

C_PList (l, [Pat l]) 

Instances

Wrapped (C_PList l0) Source # 

Associated Types

type Unwrapped (C_PList l0) :: * #

Methods

_Wrapped' :: Iso' (C_PList l0) (Unwrapped (C_PList l0)) #

(~) * (C_PList l0) t0 => Rewrapped (C_PList l1) t0 Source # 
type Unwrapped (C_PList l0) Source # 
type Unwrapped (C_PList l0) = (l0, [Pat l0])

newtype C_PParen l Source #

Constructors

C_PParen (l, Pat l) 

Instances

Wrapped (C_PParen l0) Source # 

Associated Types

type Unwrapped (C_PParen l0) :: * #

Methods

_Wrapped' :: Iso' (C_PParen l0) (Unwrapped (C_PParen l0)) #

(~) * (C_PParen l0) t0 => Rewrapped (C_PParen l1) t0 Source # 
type Unwrapped (C_PParen l0) Source # 
type Unwrapped (C_PParen l0) = (l0, Pat l0)

newtype C_PRec l Source #

Constructors

C_PRec (l, QName l, [PatField l]) 

Instances

Wrapped (C_PRec l0) Source # 

Associated Types

type Unwrapped (C_PRec l0) :: * #

Methods

_Wrapped' :: Iso' (C_PRec l0) (Unwrapped (C_PRec l0)) #

(~) * (C_PRec l0) t0 => Rewrapped (C_PRec l1) t0 Source # 
type Unwrapped (C_PRec l0) Source # 
type Unwrapped (C_PRec l0) = (l0, QName l0, [PatField l0])

newtype C_PAsPat l Source #

Constructors

C_PAsPat (l, Name l, Pat l) 

Instances

Wrapped (C_PAsPat l0) Source # 

Associated Types

type Unwrapped (C_PAsPat l0) :: * #

Methods

_Wrapped' :: Iso' (C_PAsPat l0) (Unwrapped (C_PAsPat l0)) #

(~) * (C_PAsPat l0) t0 => Rewrapped (C_PAsPat l1) t0 Source # 
type Unwrapped (C_PAsPat l0) Source # 
type Unwrapped (C_PAsPat l0) = (l0, Name l0, Pat l0)

newtype C_PWildCard l Source #

Constructors

C_PWildCard l 

Instances

Wrapped (C_PWildCard l0) Source # 

Associated Types

type Unwrapped (C_PWildCard l0) :: * #

(~) * (C_PWildCard l0) t0 => Rewrapped (C_PWildCard l1) t0 Source # 
type Unwrapped (C_PWildCard l0) Source # 
type Unwrapped (C_PWildCard l0) = l0

newtype C_PIrrPat l Source #

Constructors

C_PIrrPat (l, Pat l) 

Instances

Wrapped (C_PIrrPat l0) Source # 

Associated Types

type Unwrapped (C_PIrrPat l0) :: * #

(~) * (C_PIrrPat l0) t0 => Rewrapped (C_PIrrPat l1) t0 Source # 
type Unwrapped (C_PIrrPat l0) Source # 
type Unwrapped (C_PIrrPat l0) = (l0, Pat l0)

newtype C_PatTypeSig l Source #

Constructors

C_PatTypeSig (l, Pat l, Type l) 

Instances

Wrapped (C_PatTypeSig l0) Source # 

Associated Types

type Unwrapped (C_PatTypeSig l0) :: * #

(~) * (C_PatTypeSig l0) t0 => Rewrapped (C_PatTypeSig l1) t0 Source # 
type Unwrapped (C_PatTypeSig l0) Source # 
type Unwrapped (C_PatTypeSig l0) = (l0, Pat l0, Type l0)

newtype C_PViewPat l Source #

Constructors

C_PViewPat (l, Exp l, Pat l) 

Instances

Wrapped (C_PViewPat l0) Source # 

Associated Types

type Unwrapped (C_PViewPat l0) :: * #

(~) * (C_PViewPat l0) t0 => Rewrapped (C_PViewPat l1) t0 Source # 
type Unwrapped (C_PViewPat l0) Source # 
type Unwrapped (C_PViewPat l0) = (l0, Exp l0, Pat l0)

newtype C_PRPat l Source #

Constructors

C_PRPat (l, [RPat l]) 

Instances

Wrapped (C_PRPat l0) Source # 

Associated Types

type Unwrapped (C_PRPat l0) :: * #

Methods

_Wrapped' :: Iso' (C_PRPat l0) (Unwrapped (C_PRPat l0)) #

(~) * (C_PRPat l0) t0 => Rewrapped (C_PRPat l1) t0 Source # 
type Unwrapped (C_PRPat l0) Source # 
type Unwrapped (C_PRPat l0) = (l0, [RPat l0])

newtype C_PXTag l Source #

Constructors

C_PXTag (l, XName l, [PXAttr l], Maybe (Pat l), [Pat l]) 

Instances

Wrapped (C_PXTag l0) Source # 

Associated Types

type Unwrapped (C_PXTag l0) :: * #

Methods

_Wrapped' :: Iso' (C_PXTag l0) (Unwrapped (C_PXTag l0)) #

(~) * (C_PXTag l0) t0 => Rewrapped (C_PXTag l1) t0 Source # 
type Unwrapped (C_PXTag l0) Source # 
type Unwrapped (C_PXTag l0) = (l0, XName l0, [PXAttr l0], Maybe (Pat l0), [Pat l0])

newtype C_PXETag l Source #

Constructors

C_PXETag (l, XName l, [PXAttr l], Maybe (Pat l)) 

Instances

Wrapped (C_PXETag l0) Source # 

Associated Types

type Unwrapped (C_PXETag l0) :: * #

Methods

_Wrapped' :: Iso' (C_PXETag l0) (Unwrapped (C_PXETag l0)) #

(~) * (C_PXETag l0) t0 => Rewrapped (C_PXETag l1) t0 Source # 
type Unwrapped (C_PXETag l0) Source # 
type Unwrapped (C_PXETag l0) = (l0, XName l0, [PXAttr l0], Maybe (Pat l0))

newtype C_PXPcdata l Source #

Constructors

C_PXPcdata (l, String) 

Instances

Wrapped (C_PXPcdata l0) Source # 

Associated Types

type Unwrapped (C_PXPcdata l0) :: * #

(~) * (C_PXPcdata l0) t0 => Rewrapped (C_PXPcdata l1) t0 Source # 
type Unwrapped (C_PXPcdata l0) Source # 
type Unwrapped (C_PXPcdata l0) = (l0, String)

newtype C_PXPatTag l Source #

Constructors

C_PXPatTag (l, Pat l) 

Instances

Wrapped (C_PXPatTag l0) Source # 

Associated Types

type Unwrapped (C_PXPatTag l0) :: * #

(~) * (C_PXPatTag l0) t0 => Rewrapped (C_PXPatTag l1) t0 Source # 
type Unwrapped (C_PXPatTag l0) Source # 
type Unwrapped (C_PXPatTag l0) = (l0, Pat l0)

newtype C_PXRPats l Source #

Constructors

C_PXRPats (l, [RPat l]) 

Instances

Wrapped (C_PXRPats l0) Source # 

Associated Types

type Unwrapped (C_PXRPats l0) :: * #

(~) * (C_PXRPats l0) t0 => Rewrapped (C_PXRPats l1) t0 Source # 
type Unwrapped (C_PXRPats l0) Source # 
type Unwrapped (C_PXRPats l0) = (l0, [RPat l0])

newtype C_PQuasiQuote l Source #

Constructors

C_PQuasiQuote (l, String, String) 

Instances

Wrapped (C_PQuasiQuote l0) Source # 

Associated Types

type Unwrapped (C_PQuasiQuote l0) :: * #

(~) * (C_PQuasiQuote l0) t0 => Rewrapped (C_PQuasiQuote l1) t0 Source # 
type Unwrapped (C_PQuasiQuote l0) Source # 

newtype C_PBangPat l Source #

Constructors

C_PBangPat (l, Pat l) 

Instances

Wrapped (C_PBangPat l0) Source # 

Associated Types

type Unwrapped (C_PBangPat l0) :: * #

(~) * (C_PBangPat l0) t0 => Rewrapped (C_PBangPat l1) t0 Source # 
type Unwrapped (C_PBangPat l0) Source # 
type Unwrapped (C_PBangPat l0) = (l0, Pat l0)

newtype C_PFieldPat l Source #

Constructors

C_PFieldPat (l, QName l, Pat l) 

Instances

Wrapped (C_PFieldPat l0) Source # 

Associated Types

type Unwrapped (C_PFieldPat l0) :: * #

(~) * (C_PFieldPat l0) t0 => Rewrapped (C_PFieldPat l1) t0 Source # 
type Unwrapped (C_PFieldPat l0) Source # 
type Unwrapped (C_PFieldPat l0) = (l0, QName l0, Pat l0)

newtype C_PFieldPun l Source #

Constructors

C_PFieldPun (l, QName l) 

Instances

Wrapped (C_PFieldPun l0) Source # 

Associated Types

type Unwrapped (C_PFieldPun l0) :: * #

(~) * (C_PFieldPun l0) t0 => Rewrapped (C_PFieldPun l1) t0 Source # 
type Unwrapped (C_PFieldPun l0) Source # 
type Unwrapped (C_PFieldPun l0) = (l0, QName l0)

newtype C_RPOp l Source #

Constructors

C_RPOp (l, RPat l, RPatOp l) 

Instances

Wrapped (C_RPOp l0) Source # 

Associated Types

type Unwrapped (C_RPOp l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPOp l0) (Unwrapped (C_RPOp l0)) #

(~) * (C_RPOp l0) t0 => Rewrapped (C_RPOp l1) t0 Source # 
type Unwrapped (C_RPOp l0) Source # 
type Unwrapped (C_RPOp l0) = (l0, RPat l0, RPatOp l0)

newtype C_RPEither l Source #

Constructors

C_RPEither (l, RPat l, RPat l) 

Instances

Wrapped (C_RPEither l0) Source # 

Associated Types

type Unwrapped (C_RPEither l0) :: * #

(~) * (C_RPEither l0) t0 => Rewrapped (C_RPEither l1) t0 Source # 
type Unwrapped (C_RPEither l0) Source # 
type Unwrapped (C_RPEither l0) = (l0, RPat l0, RPat l0)

newtype C_RPSeq l Source #

Constructors

C_RPSeq (l, [RPat l]) 

Instances

Wrapped (C_RPSeq l0) Source # 

Associated Types

type Unwrapped (C_RPSeq l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPSeq l0) (Unwrapped (C_RPSeq l0)) #

(~) * (C_RPSeq l0) t0 => Rewrapped (C_RPSeq l1) t0 Source # 
type Unwrapped (C_RPSeq l0) Source # 
type Unwrapped (C_RPSeq l0) = (l0, [RPat l0])

newtype C_RPGuard l Source #

Constructors

C_RPGuard (l, Pat l, [Stmt l]) 

Instances

Wrapped (C_RPGuard l0) Source # 

Associated Types

type Unwrapped (C_RPGuard l0) :: * #

(~) * (C_RPGuard l0) t0 => Rewrapped (C_RPGuard l1) t0 Source # 
type Unwrapped (C_RPGuard l0) Source # 
type Unwrapped (C_RPGuard l0) = (l0, Pat l0, [Stmt l0])

newtype C_RPCAs l Source #

Constructors

C_RPCAs (l, Name l, RPat l) 

Instances

Wrapped (C_RPCAs l0) Source # 

Associated Types

type Unwrapped (C_RPCAs l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPCAs l0) (Unwrapped (C_RPCAs l0)) #

(~) * (C_RPCAs l0) t0 => Rewrapped (C_RPCAs l1) t0 Source # 
type Unwrapped (C_RPCAs l0) Source # 
type Unwrapped (C_RPCAs l0) = (l0, Name l0, RPat l0)

newtype C_RPAs l Source #

Constructors

C_RPAs (l, Name l, RPat l) 

Instances

Wrapped (C_RPAs l0) Source # 

Associated Types

type Unwrapped (C_RPAs l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPAs l0) (Unwrapped (C_RPAs l0)) #

(~) * (C_RPAs l0) t0 => Rewrapped (C_RPAs l1) t0 Source # 
type Unwrapped (C_RPAs l0) Source # 
type Unwrapped (C_RPAs l0) = (l0, Name l0, RPat l0)

newtype C_RPParen l Source #

Constructors

C_RPParen (l, RPat l) 

Instances

Wrapped (C_RPParen l0) Source # 

Associated Types

type Unwrapped (C_RPParen l0) :: * #

(~) * (C_RPParen l0) t0 => Rewrapped (C_RPParen l1) t0 Source # 
type Unwrapped (C_RPParen l0) Source # 
type Unwrapped (C_RPParen l0) = (l0, RPat l0)

newtype C_RPPat l Source #

Constructors

C_RPPat (l, Pat l) 

Instances

Wrapped (C_RPPat l0) Source # 

Associated Types

type Unwrapped (C_RPPat l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPPat l0) (Unwrapped (C_RPPat l0)) #

(~) * (C_RPPat l0) t0 => Rewrapped (C_RPPat l1) t0 Source # 
type Unwrapped (C_RPPat l0) Source # 
type Unwrapped (C_RPPat l0) = (l0, Pat l0)

newtype C_RPStar l Source #

Constructors

C_RPStar l 

Instances

Wrapped (C_RPStar l0) Source # 

Associated Types

type Unwrapped (C_RPStar l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPStar l0) (Unwrapped (C_RPStar l0)) #

(~) * (C_RPStar l0) t0 => Rewrapped (C_RPStar l1) t0 Source # 
type Unwrapped (C_RPStar l0) Source # 
type Unwrapped (C_RPStar l0) = l0

newtype C_RPStarG l Source #

Constructors

C_RPStarG l 

Instances

Wrapped (C_RPStarG l0) Source # 

Associated Types

type Unwrapped (C_RPStarG l0) :: * #

(~) * (C_RPStarG l0) t0 => Rewrapped (C_RPStarG l1) t0 Source # 
type Unwrapped (C_RPStarG l0) Source # 
type Unwrapped (C_RPStarG l0) = l0

newtype C_RPPlus l Source #

Constructors

C_RPPlus l 

Instances

Wrapped (C_RPPlus l0) Source # 

Associated Types

type Unwrapped (C_RPPlus l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPPlus l0) (Unwrapped (C_RPPlus l0)) #

(~) * (C_RPPlus l0) t0 => Rewrapped (C_RPPlus l1) t0 Source # 
type Unwrapped (C_RPPlus l0) Source # 
type Unwrapped (C_RPPlus l0) = l0

newtype C_RPPlusG l Source #

Constructors

C_RPPlusG l 

Instances

Wrapped (C_RPPlusG l0) Source # 

Associated Types

type Unwrapped (C_RPPlusG l0) :: * #

(~) * (C_RPPlusG l0) t0 => Rewrapped (C_RPPlusG l1) t0 Source # 
type Unwrapped (C_RPPlusG l0) Source # 
type Unwrapped (C_RPPlusG l0) = l0

newtype C_RPOpt l Source #

Constructors

C_RPOpt l 

Instances

Wrapped (C_RPOpt l0) Source # 

Associated Types

type Unwrapped (C_RPOpt l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPOpt l0) (Unwrapped (C_RPOpt l0)) #

(~) * (C_RPOpt l0) t0 => Rewrapped (C_RPOpt l1) t0 Source # 
type Unwrapped (C_RPOpt l0) Source # 
type Unwrapped (C_RPOpt l0) = l0

newtype C_RPOptG l Source #

Constructors

C_RPOptG l 

Instances

Wrapped (C_RPOptG l0) Source # 

Associated Types

type Unwrapped (C_RPOptG l0) :: * #

Methods

_Wrapped' :: Iso' (C_RPOptG l0) (Unwrapped (C_RPOptG l0)) #

(~) * (C_RPOptG l0) t0 => Rewrapped (C_RPOptG l1) t0 Source # 
type Unwrapped (C_RPOptG l0) Source # 
type Unwrapped (C_RPOptG l0) = l0

newtype C_Char l Source #

Constructors

C_Char (l, Char, String) 

Instances

Wrapped (C_Char l0) Source # 

Associated Types

type Unwrapped (C_Char l0) :: * #

Methods

_Wrapped' :: Iso' (C_Char l0) (Unwrapped (C_Char l0)) #

(~) * (C_Char l0) t0 => Rewrapped (C_Char l1) t0 Source # 
type Unwrapped (C_Char l0) Source # 
type Unwrapped (C_Char l0) = (l0, Char, String)

newtype C_String l Source #

Constructors

C_String (l, String, String) 

Instances

Wrapped (C_String l0) Source # 

Associated Types

type Unwrapped (C_String l0) :: * #

Methods

_Wrapped' :: Iso' (C_String l0) (Unwrapped (C_String l0)) #

(~) * (C_String l0) t0 => Rewrapped (C_String l1) t0 Source # 
type Unwrapped (C_String l0) Source # 
type Unwrapped (C_String l0) = (l0, String, String)

newtype C_Int l Source #

Constructors

C_Int (l, Integer, String) 

Instances

Wrapped (C_Int l0) Source # 

Associated Types

type Unwrapped (C_Int l0) :: * #

Methods

_Wrapped' :: Iso' (C_Int l0) (Unwrapped (C_Int l0)) #

(~) * (C_Int l0) t0 => Rewrapped (C_Int l1) t0 Source # 
type Unwrapped (C_Int l0) Source # 
type Unwrapped (C_Int l0) = (l0, Integer, String)

newtype C_Frac l Source #

Constructors

C_Frac (l, Rational, String) 

Instances

Wrapped (C_Frac l0) Source # 

Associated Types

type Unwrapped (C_Frac l0) :: * #

Methods

_Wrapped' :: Iso' (C_Frac l0) (Unwrapped (C_Frac l0)) #

(~) * (C_Frac l0) t0 => Rewrapped (C_Frac l1) t0 Source # 
type Unwrapped (C_Frac l0) Source # 
type Unwrapped (C_Frac l0) = (l0, Rational, String)

newtype C_PrimInt l Source #

Constructors

C_PrimInt (l, Integer, String) 

Instances

Wrapped (C_PrimInt l0) Source # 

Associated Types

type Unwrapped (C_PrimInt l0) :: * #

(~) * (C_PrimInt l0) t0 => Rewrapped (C_PrimInt l1) t0 Source # 
type Unwrapped (C_PrimInt l0) Source # 
type Unwrapped (C_PrimInt l0) = (l0, Integer, String)

newtype C_PrimWord l Source #

Constructors

C_PrimWord (l, Integer, String) 

Instances

Wrapped (C_PrimWord l0) Source # 

Associated Types

type Unwrapped (C_PrimWord l0) :: * #

(~) * (C_PrimWord l0) t0 => Rewrapped (C_PrimWord l1) t0 Source # 
type Unwrapped (C_PrimWord l0) Source # 
type Unwrapped (C_PrimWord l0) = (l0, Integer, String)

newtype C_PrimFloat l Source #

Constructors

C_PrimFloat (l, Rational, String) 

Instances

Wrapped (C_PrimFloat l0) Source # 

Associated Types

type Unwrapped (C_PrimFloat l0) :: * #

(~) * (C_PrimFloat l0) t0 => Rewrapped (C_PrimFloat l1) t0 Source # 
type Unwrapped (C_PrimFloat l0) Source # 

newtype C_PrimDouble l Source #

Constructors

C_PrimDouble (l, Rational, String) 

Instances

Wrapped (C_PrimDouble l0) Source # 

Associated Types

type Unwrapped (C_PrimDouble l0) :: * #

(~) * (C_PrimDouble l0) t0 => Rewrapped (C_PrimDouble l1) t0 Source # 
type Unwrapped (C_PrimDouble l0) Source # 

newtype C_PrimChar l Source #

Constructors

C_PrimChar (l, Char, String) 

Instances

Wrapped (C_PrimChar l0) Source # 

Associated Types

type Unwrapped (C_PrimChar l0) :: * #

(~) * (C_PrimChar l0) t0 => Rewrapped (C_PrimChar l1) t0 Source # 
type Unwrapped (C_PrimChar l0) Source # 
type Unwrapped (C_PrimChar l0) = (l0, Char, String)

newtype C_PrimString l Source #

Constructors

C_PrimString (l, String, String) 

Instances

Wrapped (C_PrimString l0) Source # 

Associated Types

type Unwrapped (C_PrimString l0) :: * #

(~) * (C_PrimString l0) t0 => Rewrapped (C_PrimString l1) t0 Source # 
type Unwrapped (C_PrimString l0) Source # 
type Unwrapped (C_PrimString l0) = (l0, String, String)

newtype C_Signless l Source #

Constructors

C_Signless l 

Instances

Wrapped (C_Signless l0) Source # 

Associated Types

type Unwrapped (C_Signless l0) :: * #

(~) * (C_Signless l0) t0 => Rewrapped (C_Signless l1) t0 Source # 
type Unwrapped (C_Signless l0) Source # 
type Unwrapped (C_Signless l0) = l0

newtype C_Negative l Source #

Constructors

C_Negative l 

Instances

Wrapped (C_Negative l0) Source # 

Associated Types

type Unwrapped (C_Negative l0) :: * #

(~) * (C_Negative l0) t0 => Rewrapped (C_Negative l1) t0 Source # 
type Unwrapped (C_Negative l0) Source # 
type Unwrapped (C_Negative l0) = l0

newtype C_Qual l Source #

Constructors

C_Qual (l, ModuleName l, Name l) 

Instances

Wrapped (C_Qual l0) Source # 

Associated Types

type Unwrapped (C_Qual l0) :: * #

Methods

_Wrapped' :: Iso' (C_Qual l0) (Unwrapped (C_Qual l0)) #

(~) * (C_Qual l0) t0 => Rewrapped (C_Qual l1) t0 Source # 
type Unwrapped (C_Qual l0) Source # 
type Unwrapped (C_Qual l0) = (l0, ModuleName l0, Name l0)

newtype C_UnQual l Source #

Constructors

C_UnQual (l, Name l) 

Instances

Wrapped (C_UnQual l0) Source # 

Associated Types

type Unwrapped (C_UnQual l0) :: * #

Methods

_Wrapped' :: Iso' (C_UnQual l0) (Unwrapped (C_UnQual l0)) #

(~) * (C_UnQual l0) t0 => Rewrapped (C_UnQual l1) t0 Source # 
type Unwrapped (C_UnQual l0) Source # 
type Unwrapped (C_UnQual l0) = (l0, Name l0)

newtype C_Special l Source #

Constructors

C_Special (l, SpecialCon l) 

Instances

Wrapped (C_Special l0) Source # 

Associated Types

type Unwrapped (C_Special l0) :: * #

(~) * (C_Special l0) t0 => Rewrapped (C_Special l1) t0 Source # 
type Unwrapped (C_Special l0) Source # 
type Unwrapped (C_Special l0) = (l0, SpecialCon l0)

newtype C_Ident l Source #

Constructors

C_Ident (l, String) 

Instances

Wrapped (C_Ident l0) Source # 

Associated Types

type Unwrapped (C_Ident l0) :: * #

Methods

_Wrapped' :: Iso' (C_Ident l0) (Unwrapped (C_Ident l0)) #

(~) * (C_Ident l0) t0 => Rewrapped (C_Ident l1) t0 Source # 
type Unwrapped (C_Ident l0) Source # 
type Unwrapped (C_Ident l0) = (l0, String)

newtype C_Symbol l Source #

Constructors

C_Symbol (l, String) 

Instances

Wrapped (C_Symbol l0) Source # 

Associated Types

type Unwrapped (C_Symbol l0) :: * #

Methods

_Wrapped' :: Iso' (C_Symbol l0) (Unwrapped (C_Symbol l0)) #

(~) * (C_Symbol l0) t0 => Rewrapped (C_Symbol l1) t0 Source # 
type Unwrapped (C_Symbol l0) Source # 
type Unwrapped (C_Symbol l0) = (l0, String)

newtype C_QVarOp l Source #

Constructors

C_QVarOp (l, QName l) 

Instances

Wrapped (C_QVarOp l0) Source # 

Associated Types

type Unwrapped (C_QVarOp l0) :: * #

Methods

_Wrapped' :: Iso' (C_QVarOp l0) (Unwrapped (C_QVarOp l0)) #

(~) * (C_QVarOp l0) t0 => Rewrapped (C_QVarOp l1) t0 Source # 
type Unwrapped (C_QVarOp l0) Source # 
type Unwrapped (C_QVarOp l0) = (l0, QName l0)

newtype C_QConOp l Source #

Constructors

C_QConOp (l, QName l) 

Instances

Wrapped (C_QConOp l0) Source # 

Associated Types

type Unwrapped (C_QConOp l0) :: * #

Methods

_Wrapped' :: Iso' (C_QConOp l0) (Unwrapped (C_QConOp l0)) #

(~) * (C_QConOp l0) t0 => Rewrapped (C_QConOp l1) t0 Source # 
type Unwrapped (C_QConOp l0) Source # 
type Unwrapped (C_QConOp l0) = (l0, QName l0)

newtype C_VarOp l Source #

Constructors

C_VarOp (l, Name l) 

Instances

Wrapped (C_VarOp l0) Source # 

Associated Types

type Unwrapped (C_VarOp l0) :: * #

Methods

_Wrapped' :: Iso' (C_VarOp l0) (Unwrapped (C_VarOp l0)) #

(~) * (C_VarOp l0) t0 => Rewrapped (C_VarOp l1) t0 Source # 
type Unwrapped (C_VarOp l0) Source # 
type Unwrapped (C_VarOp l0) = (l0, Name l0)

newtype C_ConOp l Source #

Constructors

C_ConOp (l, Name l) 

Instances

Wrapped (C_ConOp l0) Source # 

Associated Types

type Unwrapped (C_ConOp l0) :: * #

Methods

_Wrapped' :: Iso' (C_ConOp l0) (Unwrapped (C_ConOp l0)) #

(~) * (C_ConOp l0) t0 => Rewrapped (C_ConOp l1) t0 Source # 
type Unwrapped (C_ConOp l0) Source # 
type Unwrapped (C_ConOp l0) = (l0, Name l0)

newtype C_UnitCon l Source #

Constructors

C_UnitCon l 

Instances

Wrapped (C_UnitCon l0) Source # 

Associated Types

type Unwrapped (C_UnitCon l0) :: * #

(~) * (C_UnitCon l0) t0 => Rewrapped (C_UnitCon l1) t0 Source # 
type Unwrapped (C_UnitCon l0) Source # 
type Unwrapped (C_UnitCon l0) = l0

newtype C_ListCon l Source #

Constructors

C_ListCon l 

Instances

Wrapped (C_ListCon l0) Source # 

Associated Types

type Unwrapped (C_ListCon l0) :: * #

(~) * (C_ListCon l0) t0 => Rewrapped (C_ListCon l1) t0 Source # 
type Unwrapped (C_ListCon l0) Source # 
type Unwrapped (C_ListCon l0) = l0

newtype C_FunCon l Source #

Constructors

C_FunCon l 

Instances

Wrapped (C_FunCon l0) Source # 

Associated Types

type Unwrapped (C_FunCon l0) :: * #

Methods

_Wrapped' :: Iso' (C_FunCon l0) (Unwrapped (C_FunCon l0)) #

(~) * (C_FunCon l0) t0 => Rewrapped (C_FunCon l1) t0 Source # 
type Unwrapped (C_FunCon l0) Source # 
type Unwrapped (C_FunCon l0) = l0

newtype C_TupleCon l Source #

Constructors

C_TupleCon (l, Boxed, Int) 

Instances

Wrapped (C_TupleCon l0) Source # 

Associated Types

type Unwrapped (C_TupleCon l0) :: * #

(~) * (C_TupleCon l0) t0 => Rewrapped (C_TupleCon l1) t0 Source # 
type Unwrapped (C_TupleCon l0) Source # 
type Unwrapped (C_TupleCon l0) = (l0, Boxed, Int)

newtype C_Cons l Source #

Constructors

C_Cons l 

Instances

Wrapped (C_Cons l0) Source # 

Associated Types

type Unwrapped (C_Cons l0) :: * #

Methods

_Wrapped' :: Iso' (C_Cons l0) (Unwrapped (C_Cons l0)) #

(~) * (C_Cons l0) t0 => Rewrapped (C_Cons l1) t0 Source # 
type Unwrapped (C_Cons l0) Source # 
type Unwrapped (C_Cons l0) = l0

newtype C_VarName l Source #

Constructors

C_VarName (l, Name l) 

Instances

Wrapped (C_VarName l0) Source # 

Associated Types

type Unwrapped (C_VarName l0) :: * #

(~) * (C_VarName l0) t0 => Rewrapped (C_VarName l1) t0 Source # 
type Unwrapped (C_VarName l0) Source # 
type Unwrapped (C_VarName l0) = (l0, Name l0)

newtype C_ConName l Source #

Constructors

C_ConName (l, Name l) 

Instances

Wrapped (C_ConName l0) Source # 

Associated Types

type Unwrapped (C_ConName l0) :: * #

(~) * (C_ConName l0) t0 => Rewrapped (C_ConName l1) t0 Source # 
type Unwrapped (C_ConName l0) Source # 
type Unwrapped (C_ConName l0) = (l0, Name l0)

newtype C_IPDup l Source #

Constructors

C_IPDup (l, String) 

Instances

Wrapped (C_IPDup l0) Source # 

Associated Types

type Unwrapped (C_IPDup l0) :: * #

Methods

_Wrapped' :: Iso' (C_IPDup l0) (Unwrapped (C_IPDup l0)) #

(~) * (C_IPDup l0) t0 => Rewrapped (C_IPDup l1) t0 Source # 
type Unwrapped (C_IPDup l0) Source # 
type Unwrapped (C_IPDup l0) = (l0, String)

newtype C_IPLin l Source #

Constructors

C_IPLin (l, String) 

Instances

Wrapped (C_IPLin l0) Source # 

Associated Types

type Unwrapped (C_IPLin l0) :: * #

Methods

_Wrapped' :: Iso' (C_IPLin l0) (Unwrapped (C_IPLin l0)) #

(~) * (C_IPLin l0) t0 => Rewrapped (C_IPLin l1) t0 Source # 
type Unwrapped (C_IPLin l0) Source # 
type Unwrapped (C_IPLin l0) = (l0, String)

newtype C_XName l Source #

Constructors

C_XName (l, String) 

Instances

Wrapped (C_XName l0) Source # 

Associated Types

type Unwrapped (C_XName l0) :: * #

Methods

_Wrapped' :: Iso' (C_XName l0) (Unwrapped (C_XName l0)) #

(~) * (C_XName l0) t0 => Rewrapped (C_XName l1) t0 Source # 
type Unwrapped (C_XName l0) Source # 
type Unwrapped (C_XName l0) = (l0, String)

newtype C_XDomName l Source #

Constructors

C_XDomName (l, String, String) 

Instances

Wrapped (C_XDomName l0) Source # 

Associated Types

type Unwrapped (C_XDomName l0) :: * #

(~) * (C_XDomName l0) t0 => Rewrapped (C_XDomName l1) t0 Source # 
type Unwrapped (C_XDomName l0) Source # 
type Unwrapped (C_XDomName l0) = (l0, String, String)

newtype C_Nominal l Source #

Constructors

C_Nominal l 

Instances

Wrapped (C_Nominal l0) Source # 

Associated Types

type Unwrapped (C_Nominal l0) :: * #

(~) * (C_Nominal l0) t0 => Rewrapped (C_Nominal l1) t0 Source # 
type Unwrapped (C_Nominal l0) Source # 
type Unwrapped (C_Nominal l0) = l0

newtype C_Phantom l Source #

Constructors

C_Phantom l 

Instances

Wrapped (C_Phantom l0) Source # 

Associated Types

type Unwrapped (C_Phantom l0) :: * #

(~) * (C_Phantom l0) t0 => Rewrapped (C_Phantom l1) t0 Source # 
type Unwrapped (C_Phantom l0) Source # 
type Unwrapped (C_Phantom l0) = l0

newtype C_RoleWildcard l Source #

Constructors

C_RoleWildcard l 

Instances

newtype C_ExpBracket l Source #

Constructors

C_ExpBracket (l, Exp l) 

Instances

Wrapped (C_ExpBracket l0) Source # 

Associated Types

type Unwrapped (C_ExpBracket l0) :: * #

(~) * (C_ExpBracket l0) t0 => Rewrapped (C_ExpBracket l1) t0 Source # 
type Unwrapped (C_ExpBracket l0) Source # 
type Unwrapped (C_ExpBracket l0) = (l0, Exp l0)

newtype C_PatBracket l Source #

Constructors

C_PatBracket (l, Pat l) 

Instances

Wrapped (C_PatBracket l0) Source # 

Associated Types

type Unwrapped (C_PatBracket l0) :: * #

(~) * (C_PatBracket l0) t0 => Rewrapped (C_PatBracket l1) t0 Source # 
type Unwrapped (C_PatBracket l0) Source # 
type Unwrapped (C_PatBracket l0) = (l0, Pat l0)

newtype C_TypeBracket l Source #

Constructors

C_TypeBracket (l, Type l) 

Instances

Wrapped (C_TypeBracket l0) Source # 

Associated Types

type Unwrapped (C_TypeBracket l0) :: * #

(~) * (C_TypeBracket l0) t0 => Rewrapped (C_TypeBracket l1) t0 Source # 
type Unwrapped (C_TypeBracket l0) Source # 
type Unwrapped (C_TypeBracket l0) = (l0, Type l0)

newtype C_DeclBracket l Source #

Constructors

C_DeclBracket (l, [Decl l]) 

Instances

Wrapped (C_DeclBracket l0) Source # 

Associated Types

type Unwrapped (C_DeclBracket l0) :: * #

(~) * (C_DeclBracket l0) t0 => Rewrapped (C_DeclBracket l1) t0 Source # 
type Unwrapped (C_DeclBracket l0) Source # 
type Unwrapped (C_DeclBracket l0) = (l0, [Decl l0])

newtype C_IdSplice l Source #

Constructors

C_IdSplice (l, String) 

Instances

Wrapped (C_IdSplice l0) Source # 

Associated Types

type Unwrapped (C_IdSplice l0) :: * #

(~) * (C_IdSplice l0) t0 => Rewrapped (C_IdSplice l1) t0 Source # 
type Unwrapped (C_IdSplice l0) Source # 
type Unwrapped (C_IdSplice l0) = (l0, String)

newtype C_ParenSplice l Source #

Constructors

C_ParenSplice (l, Exp l) 

Instances

Wrapped (C_ParenSplice l0) Source # 

Associated Types

type Unwrapped (C_ParenSplice l0) :: * #

(~) * (C_ParenSplice l0) t0 => Rewrapped (C_ParenSplice l1) t0 Source # 
type Unwrapped (C_ParenSplice l0) Source # 
type Unwrapped (C_ParenSplice l0) = (l0, Exp l0)

newtype C_PlayRisky l Source #

Constructors

C_PlayRisky l 

Instances

Wrapped (C_PlayRisky l0) Source # 

Associated Types

type Unwrapped (C_PlayRisky l0) :: * #

(~) * (C_PlayRisky l0) t0 => Rewrapped (C_PlayRisky l1) t0 Source # 
type Unwrapped (C_PlayRisky l0) Source # 
type Unwrapped (C_PlayRisky l0) = l0

newtype C_PlaySafe l Source #

Constructors

C_PlaySafe (l, Bool) 

Instances

Wrapped (C_PlaySafe l0) Source # 

Associated Types

type Unwrapped (C_PlaySafe l0) :: * #

(~) * (C_PlaySafe l0) t0 => Rewrapped (C_PlaySafe l1) t0 Source # 
type Unwrapped (C_PlaySafe l0) Source # 
type Unwrapped (C_PlaySafe l0) = (l0, Bool)

newtype C_StdCall l Source #

Constructors

C_StdCall l 

Instances

Wrapped (C_StdCall l0) Source # 

Associated Types

type Unwrapped (C_StdCall l0) :: * #

(~) * (C_StdCall l0) t0 => Rewrapped (C_StdCall l1) t0 Source # 
type Unwrapped (C_StdCall l0) Source # 
type Unwrapped (C_StdCall l0) = l0

newtype C_CCall l Source #

Constructors

C_CCall l 

Instances

Wrapped (C_CCall l0) Source # 

Associated Types

type Unwrapped (C_CCall l0) :: * #

Methods

_Wrapped' :: Iso' (C_CCall l0) (Unwrapped (C_CCall l0)) #

(~) * (C_CCall l0) t0 => Rewrapped (C_CCall l1) t0 Source # 
type Unwrapped (C_CCall l0) Source # 
type Unwrapped (C_CCall l0) = l0

newtype C_CPlusPlus l Source #

Constructors

C_CPlusPlus l 

Instances

Wrapped (C_CPlusPlus l0) Source # 

Associated Types

type Unwrapped (C_CPlusPlus l0) :: * #

(~) * (C_CPlusPlus l0) t0 => Rewrapped (C_CPlusPlus l1) t0 Source # 
type Unwrapped (C_CPlusPlus l0) Source # 
type Unwrapped (C_CPlusPlus l0) = l0

newtype C_DotNet l Source #

Constructors

C_DotNet l 

Instances

Wrapped (C_DotNet l0) Source # 

Associated Types

type Unwrapped (C_DotNet l0) :: * #

Methods

_Wrapped' :: Iso' (C_DotNet l0) (Unwrapped (C_DotNet l0)) #

(~) * (C_DotNet l0) t0 => Rewrapped (C_DotNet l1) t0 Source # 
type Unwrapped (C_DotNet l0) Source # 
type Unwrapped (C_DotNet l0) = l0

newtype C_Jvm l Source #

Constructors

C_Jvm l 

Instances

Wrapped (C_Jvm l0) Source # 

Associated Types

type Unwrapped (C_Jvm l0) :: * #

Methods

_Wrapped' :: Iso' (C_Jvm l0) (Unwrapped (C_Jvm l0)) #

(~) * (C_Jvm l0) t0 => Rewrapped (C_Jvm l1) t0 Source # 
type Unwrapped (C_Jvm l0) Source # 
type Unwrapped (C_Jvm l0) = l0

newtype C_Js l Source #

Constructors

C_Js l 

Instances

Wrapped (C_Js l0) Source # 

Associated Types

type Unwrapped (C_Js l0) :: * #

Methods

_Wrapped' :: Iso' (C_Js l0) (Unwrapped (C_Js l0)) #

(~) * (C_Js l0) t0 => Rewrapped (C_Js l1) t0 Source # 
type Unwrapped (C_Js l0) Source # 
type Unwrapped (C_Js l0) = l0

newtype C_JavaScript l Source #

Constructors

C_JavaScript l 

Instances

Wrapped (C_JavaScript l0) Source # 

Associated Types

type Unwrapped (C_JavaScript l0) :: * #

(~) * (C_JavaScript l0) t0 => Rewrapped (C_JavaScript l1) t0 Source # 
type Unwrapped (C_JavaScript l0) Source # 
type Unwrapped (C_JavaScript l0) = l0

newtype C_CApi l Source #

Constructors

C_CApi l 

Instances

Wrapped (C_CApi l0) Source # 

Associated Types

type Unwrapped (C_CApi l0) :: * #

Methods

_Wrapped' :: Iso' (C_CApi l0) (Unwrapped (C_CApi l0)) #

(~) * (C_CApi l0) t0 => Rewrapped (C_CApi l1) t0 Source # 
type Unwrapped (C_CApi l0) Source # 
type Unwrapped (C_CApi l0) = l0

newtype C_LanguagePragma l Source #

Constructors

C_LanguagePragma (l, [Name l]) 

Instances

newtype C_OptionsPragma l Source #

Constructors

C_OptionsPragma (l, Maybe Tool, String) 

Instances

newtype C_GHC Source #

Constructors

C_GHC () 

Instances

Wrapped C_GHC Source # 

Associated Types

type Unwrapped C_GHC :: * #

(~) * C_GHC t0 => Rewrapped C_GHC t0 Source # 
type Unwrapped C_GHC Source # 
type Unwrapped C_GHC = ()

newtype C_HUGS Source #

Constructors

C_HUGS () 

Instances

Wrapped C_HUGS Source # 

Associated Types

type Unwrapped C_HUGS :: * #

(~) * C_HUGS t0 => Rewrapped C_HUGS t0 Source # 
type Unwrapped C_HUGS Source # 
type Unwrapped C_HUGS = ()

newtype C_NHC98 Source #

Constructors

C_NHC98 () 

Instances

newtype C_YHC Source #

Constructors

C_YHC () 

Instances

Wrapped C_YHC Source # 

Associated Types

type Unwrapped C_YHC :: * #

(~) * C_YHC t0 => Rewrapped C_YHC t0 Source # 
type Unwrapped C_YHC Source # 
type Unwrapped C_YHC = ()

newtype C_HADDOCK Source #

Constructors

C_HADDOCK () 

newtype C_NoOverlap l Source #

Constructors

C_NoOverlap l 

Instances

Wrapped (C_NoOverlap l0) Source # 

Associated Types

type Unwrapped (C_NoOverlap l0) :: * #

(~) * (C_NoOverlap l0) t0 => Rewrapped (C_NoOverlap l1) t0 Source # 
type Unwrapped (C_NoOverlap l0) Source # 
type Unwrapped (C_NoOverlap l0) = l0

newtype C_Overlap l Source #

Constructors

C_Overlap l 

Instances

Wrapped (C_Overlap l0) Source # 

Associated Types

type Unwrapped (C_Overlap l0) :: * #

(~) * (C_Overlap l0) t0 => Rewrapped (C_Overlap l1) t0 Source # 
type Unwrapped (C_Overlap l0) Source # 
type Unwrapped (C_Overlap l0) = l0

newtype C_Incoherent l Source #

Constructors

C_Incoherent l 

Instances

Wrapped (C_Incoherent l0) Source # 

Associated Types

type Unwrapped (C_Incoherent l0) :: * #

(~) * (C_Incoherent l0) t0 => Rewrapped (C_Incoherent l1) t0 Source # 
type Unwrapped (C_Incoherent l0) Source # 
type Unwrapped (C_Incoherent l0) = l0

newtype C_RuleVar l Source #

Constructors

C_RuleVar (l, Name l) 

Instances

Wrapped (C_RuleVar l0) Source # 

Associated Types

type Unwrapped (C_RuleVar l0) :: * #

(~) * (C_RuleVar l0) t0 => Rewrapped (C_RuleVar l1) t0 Source # 
type Unwrapped (C_RuleVar l0) Source # 
type Unwrapped (C_RuleVar l0) = (l0, Name l0)

newtype C_TypedRuleVar l Source #

Constructors

C_TypedRuleVar (l, Name l, Type l) 

Instances

Wrapped (C_TypedRuleVar l0) Source # 

Associated Types

type Unwrapped (C_TypedRuleVar l0) :: * #

(~) * (C_TypedRuleVar l0) t0 => Rewrapped (C_TypedRuleVar l1) t0 Source # 
type Unwrapped (C_TypedRuleVar l0) Source # 
type Unwrapped (C_TypedRuleVar l0) = (l0, Name l0, Type l0)

newtype C_ActiveFrom l Source #

Constructors

C_ActiveFrom (l, Int) 

Instances

Wrapped (C_ActiveFrom l0) Source # 

Associated Types

type Unwrapped (C_ActiveFrom l0) :: * #

(~) * (C_ActiveFrom l0) t0 => Rewrapped (C_ActiveFrom l1) t0 Source # 
type Unwrapped (C_ActiveFrom l0) Source # 
type Unwrapped (C_ActiveFrom l0) = (l0, Int)

newtype C_ActiveUntil l Source #

Constructors

C_ActiveUntil (l, Int) 

Instances

Wrapped (C_ActiveUntil l0) Source # 

Associated Types

type Unwrapped (C_ActiveUntil l0) :: * #

(~) * (C_ActiveUntil l0) t0 => Rewrapped (C_ActiveUntil l1) t0 Source # 
type Unwrapped (C_ActiveUntil l0) Source # 
type Unwrapped (C_ActiveUntil l0) = (l0, Int)

newtype C_Ann l Source #

Constructors

C_Ann (l, Name l, Exp l) 

Instances

Wrapped (C_Ann l0) Source # 

Associated Types

type Unwrapped (C_Ann l0) :: * #

Methods

_Wrapped' :: Iso' (C_Ann l0) (Unwrapped (C_Ann l0)) #

(~) * (C_Ann l0) t0 => Rewrapped (C_Ann l1) t0 Source # 
type Unwrapped (C_Ann l0) Source # 
type Unwrapped (C_Ann l0) = (l0, Name l0, Exp l0)

newtype C_TypeAnn l Source #

Constructors

C_TypeAnn (l, Name l, Exp l) 

Instances

Wrapped (C_TypeAnn l0) Source # 

Associated Types

type Unwrapped (C_TypeAnn l0) :: * #

(~) * (C_TypeAnn l0) t0 => Rewrapped (C_TypeAnn l1) t0 Source # 
type Unwrapped (C_TypeAnn l0) Source # 
type Unwrapped (C_TypeAnn l0) = (l0, Name l0, Exp l0)

newtype C_ModuleAnn l Source #

Constructors

C_ModuleAnn (l, Exp l) 

Instances

Wrapped (C_ModuleAnn l0) Source # 

Associated Types

type Unwrapped (C_ModuleAnn l0) :: * #

(~) * (C_ModuleAnn l0) t0 => Rewrapped (C_ModuleAnn l1) t0 Source # 
type Unwrapped (C_ModuleAnn l0) Source # 
type Unwrapped (C_ModuleAnn l0) = (l0, Exp l0)

newtype C_VarFormula l Source #

Constructors

C_VarFormula (l, Name l) 

Instances

Wrapped (C_VarFormula l0) Source # 

Associated Types

type Unwrapped (C_VarFormula l0) :: * #

(~) * (C_VarFormula l0) t0 => Rewrapped (C_VarFormula l1) t0 Source # 
type Unwrapped (C_VarFormula l0) Source # 
type Unwrapped (C_VarFormula l0) = (l0, Name l0)

newtype C_AndFormula l Source #

Constructors

C_AndFormula (l, [BooleanFormula l]) 

Instances

Wrapped (C_AndFormula l0) Source # 

Associated Types

type Unwrapped (C_AndFormula l0) :: * #

(~) * (C_AndFormula l0) t0 => Rewrapped (C_AndFormula l1) t0 Source # 
type Unwrapped (C_AndFormula l0) Source # 
type Unwrapped (C_AndFormula l0) = (l0, [BooleanFormula l0])

newtype C_OrFormula l Source #

Constructors

C_OrFormula (l, [BooleanFormula l]) 

Instances

Wrapped (C_OrFormula l0) Source # 

Associated Types

type Unwrapped (C_OrFormula l0) :: * #

(~) * (C_OrFormula l0) t0 => Rewrapped (C_OrFormula l1) t0 Source # 
type Unwrapped (C_OrFormula l0) Source # 
type Unwrapped (C_OrFormula l0) = (l0, [BooleanFormula l0])

newtype C_ParenFormula l Source #

Constructors

C_ParenFormula (l, BooleanFormula l) 

Instances

_Do' :: Prism' (Exp v) (C_Do v) Source #

_If' :: Prism' (Exp v) (C_If v) Source #