{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Haskell.Syntax.Type (
HsScaled(..),
hsMult, hsScaledThing,
HsArrow(..),
HsLinearArrowTokens(..),
HsType(..), LHsType, HsKind, LHsKind,
HsForAllTelescope(..), HsTyVarBndr(..), LHsTyVarBndr,
LHsQTyVars(..),
HsOuterTyVarBndrs(..), HsOuterFamEqnTyVarBndrs, HsOuterSigTyVarBndrs,
HsWildCardBndrs(..),
HsPatSigType(..),
HsSigType(..), LHsSigType, LHsSigWcType, LHsWcType,
HsTupleSort(..),
HsContext, LHsContext,
HsTyLit(..),
HsIPName(..), hsIPNameFS,
HsArg(..),
LHsTypeArg,
LBangType, BangType,
HsSrcBang(..),
PromotionFlag(..), isPromoted,
ConDeclField(..), LConDeclField,
HsConDetails(..), noTypeArgs,
FieldOcc(..), LFieldOcc,
AmbiguousFieldOcc(..), LAmbiguousFieldOcc,
mapHsOuterImplicit,
hsQTvExplicit,
isHsKindedTyVar,
hsPatSigType,
) where
import {-# SOURCE #-} Language.Haskell.Syntax.Expr ( HsUntypedSplice )
import Language.Haskell.Syntax.Concrete
import Language.Haskell.Syntax.Extension
import GHC.Types.Name.Reader ( RdrName )
import GHC.Core.DataCon( HsSrcBang(..) )
import GHC.Core.Type (Specificity)
import GHC.Types.SrcLoc (SrcSpan)
import GHC.Hs.Doc (LHsDoc)
import GHC.Data.FastString (FastString)
import Data.Data hiding ( Fixity, Prefix, Infix )
import Data.Void
import Data.Maybe
import Data.Eq
import Data.Bool
import Data.Char
import Prelude (Integer)
data PromotionFlag
= NotPromoted
| IsPromoted
deriving ( PromotionFlag -> PromotionFlag -> Bool
(PromotionFlag -> PromotionFlag -> Bool)
-> (PromotionFlag -> PromotionFlag -> Bool) -> Eq PromotionFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromotionFlag -> PromotionFlag -> Bool
== :: PromotionFlag -> PromotionFlag -> Bool
$c/= :: PromotionFlag -> PromotionFlag -> Bool
/= :: PromotionFlag -> PromotionFlag -> Bool
Eq, Typeable PromotionFlag
Typeable PromotionFlag =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag)
-> (PromotionFlag -> Constr)
-> (PromotionFlag -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag))
-> ((forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r)
-> (forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag)
-> Data PromotionFlag
PromotionFlag -> Constr
PromotionFlag -> DataType
(forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u
forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PromotionFlag
$ctoConstr :: PromotionFlag -> Constr
toConstr :: PromotionFlag -> Constr
$cdataTypeOf :: PromotionFlag -> DataType
dataTypeOf :: PromotionFlag -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PromotionFlag)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PromotionFlag)
$cgmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag
gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> PromotionFlag -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag
Data )
isPromoted :: PromotionFlag -> Bool
isPromoted :: PromotionFlag -> Bool
isPromoted PromotionFlag
IsPromoted = Bool
True
isPromoted PromotionFlag
NotPromoted = Bool
False
type LBangType pass = XRec pass (BangType pass)
type BangType pass = HsType pass
type LHsContext pass = XRec pass (HsContext pass)
type HsContext pass = [LHsType pass]
type LHsType pass = XRec pass (HsType pass)
type HsKind pass = HsType pass
type LHsKind pass = XRec pass (HsKind pass)
data HsForAllTelescope pass
= HsForAllVis
{ forall pass. HsForAllTelescope pass -> XHsForAllVis pass
hsf_xvis :: XHsForAllVis pass
, forall pass. HsForAllTelescope pass -> [LHsTyVarBndr () pass]
hsf_vis_bndrs :: [LHsTyVarBndr () pass]
}
| HsForAllInvis
{ forall pass. HsForAllTelescope pass -> XHsForAllInvis pass
hsf_xinvis :: XHsForAllInvis pass
, forall pass.
HsForAllTelescope pass -> [LHsTyVarBndr Specificity pass]
hsf_invis_bndrs :: [LHsTyVarBndr Specificity pass]
}
| XHsForAllTelescope !(XXHsForAllTelescope pass)
type LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass)
data LHsQTyVars pass
= HsQTvs { forall pass. LHsQTyVars pass -> XHsQTvs pass
hsq_ext :: XHsQTvs pass
, forall pass. LHsQTyVars pass -> [LHsTyVarBndr () pass]
hsq_explicit :: [LHsTyVarBndr () pass]
}
| XLHsQTyVars !(XXLHsQTyVars pass)
hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr () pass]
hsQTvExplicit :: forall pass. LHsQTyVars pass -> [LHsTyVarBndr () pass]
hsQTvExplicit = LHsQTyVars pass -> [LHsTyVarBndr () pass]
forall pass. LHsQTyVars pass -> [LHsTyVarBndr () pass]
hsq_explicit
data HsOuterTyVarBndrs flag pass
= HsOuterImplicit
{ forall flag pass.
HsOuterTyVarBndrs flag pass -> XHsOuterImplicit pass
hso_ximplicit :: XHsOuterImplicit pass
}
| HsOuterExplicit
{ forall flag pass.
HsOuterTyVarBndrs flag pass -> XHsOuterExplicit pass flag
hso_xexplicit :: XHsOuterExplicit pass flag
, forall flag pass.
HsOuterTyVarBndrs flag pass -> [LHsTyVarBndr flag (NoGhcTc pass)]
hso_bndrs :: [LHsTyVarBndr flag (NoGhcTc pass)]
}
| XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass)
type HsOuterSigTyVarBndrs = HsOuterTyVarBndrs Specificity
type HsOuterFamEqnTyVarBndrs = HsOuterTyVarBndrs ()
data HsWildCardBndrs pass thing
= HsWC { forall pass thing. HsWildCardBndrs pass thing -> XHsWC pass thing
hswc_ext :: XHsWC pass thing
, forall pass thing. HsWildCardBndrs pass thing -> thing
hswc_body :: thing
}
| XHsWildCardBndrs !(XXHsWildCardBndrs pass thing)
data HsPatSigType pass
= HsPS { forall pass. HsPatSigType pass -> XHsPS pass
hsps_ext :: XHsPS pass
, forall pass. HsPatSigType pass -> LHsType pass
hsps_body :: LHsType pass
}
| XHsPatSigType !(XXHsPatSigType pass)
type LHsSigType pass = XRec pass (HsSigType pass)
type LHsWcType pass = HsWildCardBndrs pass (LHsType pass)
type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass)
data HsSigType pass
= HsSig { forall pass. HsSigType pass -> XHsSig pass
sig_ext :: XHsSig pass
, forall pass. HsSigType pass -> HsOuterSigTyVarBndrs pass
sig_bndrs :: HsOuterSigTyVarBndrs pass
, forall pass. HsSigType pass -> LHsType pass
sig_body :: LHsType pass
}
| XHsSigType !(XXHsSigType pass)
hsPatSigType :: HsPatSigType pass -> LHsType pass
hsPatSigType :: forall pass. HsPatSigType pass -> LHsType pass
hsPatSigType = HsPatSigType pass -> LHsType pass
forall pass. HsPatSigType pass -> LHsType pass
hsps_body
mapHsOuterImplicit :: (XHsOuterImplicit pass -> XHsOuterImplicit pass)
-> HsOuterTyVarBndrs flag pass
-> HsOuterTyVarBndrs flag pass
mapHsOuterImplicit :: forall pass flag.
(XHsOuterImplicit pass -> XHsOuterImplicit pass)
-> HsOuterTyVarBndrs flag pass -> HsOuterTyVarBndrs flag pass
mapHsOuterImplicit XHsOuterImplicit pass -> XHsOuterImplicit pass
f (HsOuterImplicit{hso_ximplicit :: forall flag pass.
HsOuterTyVarBndrs flag pass -> XHsOuterImplicit pass
hso_ximplicit = XHsOuterImplicit pass
imp}) =
HsOuterImplicit{hso_ximplicit :: XHsOuterImplicit pass
hso_ximplicit = XHsOuterImplicit pass -> XHsOuterImplicit pass
f XHsOuterImplicit pass
imp}
mapHsOuterImplicit XHsOuterImplicit pass -> XHsOuterImplicit pass
_ hso :: HsOuterTyVarBndrs flag pass
hso@(HsOuterExplicit{}) = HsOuterTyVarBndrs flag pass
hso
mapHsOuterImplicit XHsOuterImplicit pass -> XHsOuterImplicit pass
_ hso :: HsOuterTyVarBndrs flag pass
hso@(XHsOuterTyVarBndrs{}) = HsOuterTyVarBndrs flag pass
hso
newtype HsIPName = HsIPName FastString
deriving( HsIPName -> HsIPName -> Bool
(HsIPName -> HsIPName -> Bool)
-> (HsIPName -> HsIPName -> Bool) -> Eq HsIPName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HsIPName -> HsIPName -> Bool
== :: HsIPName -> HsIPName -> Bool
$c/= :: HsIPName -> HsIPName -> Bool
/= :: HsIPName -> HsIPName -> Bool
Eq, Typeable HsIPName
Typeable HsIPName =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsIPName -> c HsIPName)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsIPName)
-> (HsIPName -> Constr)
-> (HsIPName -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsIPName))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName))
-> ((forall b. Data b => b -> b) -> HsIPName -> HsIPName)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r)
-> (forall u. (forall d. Data d => d -> u) -> HsIPName -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> HsIPName -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName)
-> Data HsIPName
HsIPName -> Constr
HsIPName -> DataType
(forall b. Data b => b -> b) -> HsIPName -> HsIPName
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> HsIPName -> u
forall u. (forall d. Data d => d -> u) -> HsIPName -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsIPName
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsIPName -> c HsIPName
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsIPName)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsIPName -> c HsIPName
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsIPName -> c HsIPName
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsIPName
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsIPName
$ctoConstr :: HsIPName -> Constr
toConstr :: HsIPName -> Constr
$cdataTypeOf :: HsIPName -> DataType
dataTypeOf :: HsIPName -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsIPName)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsIPName)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName)
$cgmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName
gmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsIPName -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HsIPName -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HsIPName -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HsIPName -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HsIPName -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsIPName -> m HsIPName
Data )
hsIPNameFS :: HsIPName -> FastString
hsIPNameFS :: HsIPName -> FastString
hsIPNameFS (HsIPName FastString
n) = FastString
n
data HsTyVarBndr flag pass
= UserTyVar
(XUserTyVar pass)
flag
(LIdP pass)
| KindedTyVar
(XKindedTyVar pass)
flag
(LIdP pass)
(LHsKind pass)
| XTyVarBndr
!(XXTyVarBndr pass)
isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool
isHsKindedTyVar :: forall flag pass. HsTyVarBndr flag pass -> Bool
isHsKindedTyVar (UserTyVar {}) = Bool
False
isHsKindedTyVar (KindedTyVar {}) = Bool
True
isHsKindedTyVar (XTyVarBndr {}) = Bool
False
data HsType pass
= HsForAllTy
{ forall pass. HsType pass -> XForAllTy pass
hst_xforall :: XForAllTy pass
, forall pass. HsType pass -> HsForAllTelescope pass
hst_tele :: HsForAllTelescope pass
, forall pass. HsType pass -> LHsType pass
hst_body :: LHsType pass
}
| HsQualTy
{ forall pass. HsType pass -> XQualTy pass
hst_xqual :: XQualTy pass
, forall pass. HsType pass -> LHsContext pass
hst_ctxt :: LHsContext pass
, hst_body :: LHsType pass }
| HsTyVar (XTyVar pass)
PromotionFlag
(LIdP pass)
| HsAppTy (XAppTy pass)
(LHsType pass)
(LHsType pass)
| HsAppKindTy (XAppKindTy pass)
(LHsType pass)
(LHsKind pass)
| HsFunTy (XFunTy pass)
(HsArrow pass)
(LHsType pass)
(LHsType pass)
| HsListTy (XListTy pass)
(LHsType pass)
| HsTupleTy (XTupleTy pass)
HsTupleSort
[LHsType pass]
| HsSumTy (XSumTy pass)
[LHsType pass]
| HsOpTy (XOpTy pass)
PromotionFlag
(LHsType pass) (LIdP pass) (LHsType pass)
| HsParTy (XParTy pass)
(LHsType pass)
| HsIParamTy (XIParamTy pass)
(XRec pass HsIPName)
(LHsType pass)
| HsStarTy (XStarTy pass)
Bool
| HsKindSig (XKindSig pass)
(LHsType pass)
(LHsKind pass)
| HsSpliceTy (XSpliceTy pass)
(HsUntypedSplice pass)
| HsDocTy (XDocTy pass)
(LHsType pass) (LHsDoc pass)
| HsBangTy (XBangTy pass)
HsSrcBang (LHsType pass)
| HsRecTy (XRecTy pass)
[LConDeclField pass]
| HsExplicitListTy
(XExplicitListTy pass)
PromotionFlag
[LHsType pass]
| HsExplicitTupleTy
(XExplicitTupleTy pass)
[LHsType pass]
| HsTyLit (XTyLit pass) (HsTyLit pass)
| HsWildCardTy (XWildCardTy pass)
| XHsType
!(XXType pass)
data HsTyLit pass
= HsNumTy (XNumTy pass) Integer
| HsStrTy (XStrTy pass) FastString
| HsCharTy (XCharTy pass) Char
| XTyLit !(XXTyLit pass)
data HsArrow pass
= HsUnrestrictedArrow !(LHsUniToken "->" "→" pass)
| HsLinearArrow !(HsLinearArrowTokens pass)
| HsExplicitMult !(LHsToken "%" pass) !(LHsType pass) !(LHsUniToken "->" "→" pass)
data HsLinearArrowTokens pass
= HsPct1 !(LHsToken "%1" pass) !(LHsUniToken "->" "→" pass)
| HsLolly !(LHsToken "⊸" pass)
data HsScaled pass a = HsScaled (HsArrow pass) a
hsMult :: HsScaled pass a -> HsArrow pass
hsMult :: forall pass a. HsScaled pass a -> HsArrow pass
hsMult (HsScaled HsArrow pass
m a
_) = HsArrow pass
m
hsScaledThing :: HsScaled pass a -> a
hsScaledThing :: forall pass a. HsScaled pass a -> a
hsScaledThing (HsScaled HsArrow pass
_ a
t) = a
t
data HsTupleSort = HsUnboxedTuple
| HsBoxedOrConstraintTuple
deriving Typeable HsTupleSort
Typeable HsTupleSort =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsTupleSort)
-> (HsTupleSort -> Constr)
-> (HsTupleSort -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsTupleSort))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsTupleSort))
-> ((forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r)
-> (forall u. (forall d. Data d => d -> u) -> HsTupleSort -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort)
-> Data HsTupleSort
HsTupleSort -> Constr
HsTupleSort -> DataType
(forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u
forall u. (forall d. Data d => d -> u) -> HsTupleSort -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsTupleSort
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsTupleSort)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsTupleSort)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsTupleSort
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsTupleSort
$ctoConstr :: HsTupleSort -> Constr
toConstr :: HsTupleSort -> Constr
$cdataTypeOf :: HsTupleSort -> DataType
dataTypeOf :: HsTupleSort -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsTupleSort)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsTupleSort)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsTupleSort)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HsTupleSort)
$cgmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort
gmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HsTupleSort -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HsTupleSort -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort
Data
type LConDeclField pass = XRec pass (ConDeclField pass)
data ConDeclField pass
= ConDeclField { forall pass. ConDeclField pass -> XConDeclField pass
cd_fld_ext :: XConDeclField pass,
forall pass. ConDeclField pass -> [LFieldOcc pass]
cd_fld_names :: [LFieldOcc pass],
forall pass. ConDeclField pass -> LBangType pass
cd_fld_type :: LBangType pass,
forall pass. ConDeclField pass -> Maybe (LHsDoc pass)
cd_fld_doc :: Maybe (LHsDoc pass)}
| XConDeclField !(XXConDeclField pass)
data HsConDetails tyarg arg rec
= PrefixCon [tyarg] [arg]
| RecCon rec
| InfixCon arg arg
deriving Typeable (HsConDetails tyarg arg rec)
Typeable (HsConDetails tyarg arg rec) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HsConDetails tyarg arg rec
-> c (HsConDetails tyarg arg rec))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c (HsConDetails tyarg arg rec))
-> (HsConDetails tyarg arg rec -> Constr)
-> (HsConDetails tyarg arg rec -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (HsConDetails tyarg arg rec)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HsConDetails tyarg arg rec)))
-> ((forall b. Data b => b -> b)
-> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec))
-> Data (HsConDetails tyarg arg rec)
HsConDetails tyarg arg rec -> Constr
HsConDetails tyarg arg rec -> DataType
(forall b. Data b => b -> b)
-> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u
forall u.
(forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
Typeable (HsConDetails tyarg arg rec)
forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
HsConDetails tyarg arg rec -> Constr
forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
HsConDetails tyarg arg rec -> DataType
forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
(forall b. Data b => b -> b)
-> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec
forall tyarg arg rec u.
(Data tyarg, Data rec, Data arg) =>
Int
-> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u
forall tyarg arg rec u.
(Data tyarg, Data rec, Data arg) =>
(forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u]
forall tyarg arg rec r r'.
(Data tyarg, Data rec, Data arg) =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
forall tyarg arg rec r r'.
(Data tyarg, Data rec, Data arg) =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
forall tyarg arg rec (m :: * -> *).
(Data tyarg, Data rec, Data arg, Monad m) =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
forall tyarg arg rec (m :: * -> *).
(Data tyarg, Data rec, Data arg, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
forall tyarg arg rec (c :: * -> *).
(Data tyarg, Data rec, Data arg) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec)
forall tyarg arg rec (c :: * -> *).
(Data tyarg, Data rec, Data arg) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HsConDetails tyarg arg rec
-> c (HsConDetails tyarg arg rec)
forall tyarg arg rec (t :: * -> *) (c :: * -> *).
(Data tyarg, Data rec, Data arg, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (HsConDetails tyarg arg rec))
forall tyarg arg rec (t :: * -> * -> *) (c :: * -> *).
(Data tyarg, Data rec, Data arg, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HsConDetails tyarg arg rec))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HsConDetails tyarg arg rec
-> c (HsConDetails tyarg arg rec)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (HsConDetails tyarg arg rec))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HsConDetails tyarg arg rec))
$cgfoldl :: forall tyarg arg rec (c :: * -> *).
(Data tyarg, Data rec, Data arg) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HsConDetails tyarg arg rec
-> c (HsConDetails tyarg arg rec)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HsConDetails tyarg arg rec
-> c (HsConDetails tyarg arg rec)
$cgunfold :: forall tyarg arg rec (c :: * -> *).
(Data tyarg, Data rec, Data arg) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec)
$ctoConstr :: forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
HsConDetails tyarg arg rec -> Constr
toConstr :: HsConDetails tyarg arg rec -> Constr
$cdataTypeOf :: forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
HsConDetails tyarg arg rec -> DataType
dataTypeOf :: HsConDetails tyarg arg rec -> DataType
$cdataCast1 :: forall tyarg arg rec (t :: * -> *) (c :: * -> *).
(Data tyarg, Data rec, Data arg, Typeable t) =>
(forall d. Data d => c (t d))
-> Maybe (c (HsConDetails tyarg arg rec))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c (HsConDetails tyarg arg rec))
$cdataCast2 :: forall tyarg arg rec (t :: * -> * -> *) (c :: * -> *).
(Data tyarg, Data rec, Data arg, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HsConDetails tyarg arg rec))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (HsConDetails tyarg arg rec))
$cgmapT :: forall tyarg arg rec.
(Data tyarg, Data rec, Data arg) =>
(forall b. Data b => b -> b)
-> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec
gmapT :: (forall b. Data b => b -> b)
-> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec
$cgmapQl :: forall tyarg arg rec r r'.
(Data tyarg, Data rec, Data arg) =>
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
$cgmapQr :: forall tyarg arg rec r r'.
(Data tyarg, Data rec, Data arg) =>
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HsConDetails tyarg arg rec
-> r
$cgmapQ :: forall tyarg arg rec u.
(Data tyarg, Data rec, Data arg) =>
(forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u]
$cgmapQi :: forall tyarg arg rec u.
(Data tyarg, Data rec, Data arg) =>
Int
-> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u
$cgmapM :: forall tyarg arg rec (m :: * -> *).
(Data tyarg, Data rec, Data arg, Monad m) =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
$cgmapMp :: forall tyarg arg rec (m :: * -> *).
(Data tyarg, Data rec, Data arg, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
$cgmapMo :: forall tyarg arg rec (m :: * -> *).
(Data tyarg, Data rec, Data arg, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec)
Data
noTypeArgs :: [Void]
noTypeArgs :: [Void]
noTypeArgs = []
data HsArg tm ty
= HsValArg tm
| HsTypeArg SrcSpan ty
| HsArgPar SrcSpan
type LHsTypeArg p = HsArg (LHsType p) (LHsKind p)
type LFieldOcc pass = XRec pass (FieldOcc pass)
data FieldOcc pass
= FieldOcc {
forall pass. FieldOcc pass -> XCFieldOcc pass
foExt :: XCFieldOcc pass
, forall pass. FieldOcc pass -> XRec pass RdrName
foLabel :: XRec pass RdrName
}
| XFieldOcc !(XXFieldOcc pass)
deriving instance (
Eq (XRec pass RdrName)
, Eq (XCFieldOcc pass)
, Eq (XXFieldOcc pass)
) => Eq (FieldOcc pass)
type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass)
data AmbiguousFieldOcc pass
= Unambiguous (XUnambiguous pass) (XRec pass RdrName)
| Ambiguous (XAmbiguous pass) (XRec pass RdrName)
| XAmbiguousFieldOcc !(XXAmbiguousFieldOcc pass)