Safe Haskell | None |
---|---|
Language | Haskell98 |
Language.Haskell.Liquid.Types.DataDecl
Description
This module contains types to represent refined data types.
Synopsis
- type DataDecl = DataDeclP Symbol BareType
- type DataDeclLHName = DataDeclP LHName BareTypeLHName
- type DataDeclParsed = DataDeclP LocSymbol BareTypeParsed
- data DataDeclP v ty = DataDecl {}
- data DataName
- dataNameSymbol :: DataName -> Located LHName
- type DataCtor = DataCtorP BareType
- type DataCtorParsed = DataCtorP BareTypeParsed
- data DataCtorP ty = DataCtor {}
- data DataConP = DataConP {}
- data HasDataDecl
- hasDecl :: DataDecl -> HasDataDecl
- data DataDeclKind
- data TyConP = TyConP {
- tcpLoc :: !SourcePos
- tcpCon :: !TyCon
- tcpFreeTyVarsTy :: ![RTyVar]
- tcpFreePredTy :: ![PVar RSort]
- tcpVarianceTs :: !VarianceInfo
- tcpVariancePs :: !VarianceInfo
- tcpSizeFun :: !(Maybe SizeFun)
Parse-time entities describing refined data types
Constructors
DataDecl | |
Fields
|
Instances
The name of the TyCon
corresponding to a DataDecl
Constructors
DnName !(Located LHName) | for |
DnCon !(Located LHName) | for |
Instances
Binary DataName Source # | |||||
Data DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataName -> c DataName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataName # toConstr :: DataName -> Constr # dataTypeOf :: DataName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataName) # gmapT :: (forall b. Data b => b -> b) -> DataName -> DataName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataName -> r # gmapQ :: (forall d. Data d => d -> u) -> DataName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataName -> m DataName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataName -> m DataName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataName -> m DataName # | |||||
Generic DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Associated Types
| |||||
Show DataName Source # | |||||
Eq DataName Source # | |||||
Ord DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
Hashable DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
PPrint DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
Loc DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
type Rep DataName Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl type Rep DataName = D1 ('MetaData "DataName" "Language.Haskell.Liquid.Types.DataDecl" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "DnName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Located LHName))) :+: C1 ('MetaCons "DnCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Located LHName)))) |
type DataCtorParsed = DataCtorP BareTypeParsed Source #
Constructors
DataCtor | |
Instances
Functor DataCtorP Source # | |||||
Foldable DataCtorP Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods fold :: Monoid m => DataCtorP m -> m # foldMap :: Monoid m => (a -> m) -> DataCtorP a -> m # foldMap' :: Monoid m => (a -> m) -> DataCtorP a -> m # foldr :: (a -> b -> b) -> b -> DataCtorP a -> b # foldr' :: (a -> b -> b) -> b -> DataCtorP a -> b # foldl :: (b -> a -> b) -> b -> DataCtorP a -> b # foldl' :: (b -> a -> b) -> b -> DataCtorP a -> b # foldr1 :: (a -> a -> a) -> DataCtorP a -> a # foldl1 :: (a -> a -> a) -> DataCtorP a -> a # toList :: DataCtorP a -> [a] # length :: DataCtorP a -> Int # elem :: Eq a => a -> DataCtorP a -> Bool # maximum :: Ord a => DataCtorP a -> a # minimum :: Ord a => DataCtorP a -> a # | |||||
Traversable DataCtorP Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
Expand DataCtor Source # | |||||
Binary ty => Binary (DataCtorP ty) Source # | |||||
Data ty => Data (DataCtorP ty) Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCtorP ty -> c (DataCtorP ty) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataCtorP ty) # toConstr :: DataCtorP ty -> Constr # dataTypeOf :: DataCtorP ty -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataCtorP ty)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataCtorP ty)) # gmapT :: (forall b. Data b => b -> b) -> DataCtorP ty -> DataCtorP ty # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCtorP ty -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCtorP ty -> r # gmapQ :: (forall d. Data d => d -> u) -> DataCtorP ty -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCtorP ty -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCtorP ty -> m (DataCtorP ty) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCtorP ty -> m (DataCtorP ty) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCtorP ty -> m (DataCtorP ty) # | |||||
Generic (DataCtorP ty) Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Associated Types
| |||||
Eq ty => Eq (DataCtorP ty) Source # | |||||
Hashable ty => Hashable (DataCtorP ty) Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
PPrint ty => PPrint (DataCtorP ty) Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
Loc (DataCtorP ty) Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
type Rep (DataCtorP ty) Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl type Rep (DataCtorP ty) = D1 ('MetaData "DataCtorP" "Language.Haskell.Liquid.Types.DataDecl" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "DataCtor" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dcName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Located LHName)) :*: S1 ('MetaSel ('Just "dcTyVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Symbol])) :*: (S1 ('MetaSel ('Just "dcTheta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ty]) :*: (S1 ('MetaSel ('Just "dcFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(LHName, ty)]) :*: S1 ('MetaSel ('Just "dcResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ty)))))) |
Constructors
DataConP | |
Fields
|
Instances
Data DataConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataConP -> c DataConP # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataConP # toConstr :: DataConP -> Constr # dataTypeOf :: DataConP -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataConP) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataConP) # gmapT :: (forall b. Data b => b -> b) -> DataConP -> DataConP # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataConP -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataConP -> r # gmapQ :: (forall d. Data d => d -> u) -> DataConP -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataConP -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataConP -> m DataConP # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataConP -> m DataConP # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataConP -> m DataConP # | |||||
Generic DataConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Associated Types
| |||||
PPrint SpecType => Show DataConP Source # | |||||
PPrint SpecType => PPrint DataConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
Loc DataConP Source # |
Here the | ||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
type Rep DataConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl type Rep DataConP = D1 ('MetaData "DataConP" "Language.Haskell.Liquid.Types.DataDecl" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "DataConP" 'PrefixI 'True) (((S1 ('MetaSel ('Just "dcpLoc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "dcpCon") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataCon)) :*: (S1 ('MetaSel ('Just "dcpFreeTyVars") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RTyVar]) :*: (S1 ('MetaSel ('Just "dcpFreePred") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PVar RSort]) :*: S1 ('MetaSel ('Just "dcpTyConstrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [SpecType])))) :*: ((S1 ('MetaSel ('Just "dcpTyArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(LHName, SpecType)]) :*: S1 ('MetaSel ('Just "dcpTyRes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecType)) :*: (S1 ('MetaSel ('Just "dcpIsGadt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "dcpModule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Symbol) :*: S1 ('MetaSel ('Just "dcpLocE") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos)))))) |
data HasDataDecl Source #
Instances
Show HasDataDecl Source # | |
Defined in Language.Haskell.Liquid.Types.DataDecl Methods showsPrec :: Int -> HasDataDecl -> ShowS # show :: HasDataDecl -> String # showList :: [HasDataDecl] -> ShowS # | |
PPrint HasDataDecl Source # | |
Defined in Language.Haskell.Liquid.Types.DataDecl |
hasDecl :: DataDecl -> HasDataDecl Source #
data DataDeclKind Source #
What kind of DataDecl
is it?
Constructors
DataUser | User defined data-definitions (should have refined fields) |
DataReflected | Automatically lifted data-definitions (do not have refined fields) |
Instances
Binary DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
NFData DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods rnf :: DataDeclKind -> () # | |||||
Data DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataDeclKind -> c DataDeclKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataDeclKind # toConstr :: DataDeclKind -> Constr # dataTypeOf :: DataDeclKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataDeclKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataDeclKind) # gmapT :: (forall b. Data b => b -> b) -> DataDeclKind -> DataDeclKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclKind -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclKind -> r # gmapQ :: (forall d. Data d => d -> u) -> DataDeclKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataDeclKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataDeclKind -> m DataDeclKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclKind -> m DataDeclKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclKind -> m DataDeclKind # | |||||
Generic DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Associated Types
| |||||
Show DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl Methods showsPrec :: Int -> DataDeclKind -> ShowS # show :: DataDeclKind -> String # showList :: [DataDeclKind] -> ShowS # | |||||
Eq DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
Hashable DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl | |||||
type Rep DataDeclKind Source # | |||||
Defined in Language.Haskell.Liquid.Types.DataDecl |
Constructors
TyConP | |
Fields
|
Instances
Data TyConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.RType Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyConP -> c TyConP # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyConP # toConstr :: TyConP -> Constr # dataTypeOf :: TyConP -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyConP) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyConP) # gmapT :: (forall b. Data b => b -> b) -> TyConP -> TyConP # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyConP -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyConP -> r # gmapQ :: (forall d. Data d => d -> u) -> TyConP -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyConP -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyConP -> m TyConP # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyConP -> m TyConP # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyConP -> m TyConP # | |||||
Generic TyConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.RType Associated Types
| |||||
Show TyConP Source # | |||||
PPrint TyConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.RType | |||||
Loc TyConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.RType | |||||
type Rep TyConP Source # | |||||
Defined in Language.Haskell.Liquid.Types.RType type Rep TyConP = D1 ('MetaData "TyConP" "Language.Haskell.Liquid.Types.RType" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "TyConP" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tcpLoc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "tcpCon") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TyCon) :*: S1 ('MetaSel ('Just "tcpFreeTyVarsTy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RTyVar]))) :*: ((S1 ('MetaSel ('Just "tcpFreePredTy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PVar RSort]) :*: S1 ('MetaSel ('Just "tcpVarianceTs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarianceInfo)) :*: (S1 ('MetaSel ('Just "tcpVariancePs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarianceInfo) :*: S1 ('MetaSel ('Just "tcpSizeFun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe SizeFun)))))) |