liquidhaskell-boot-0.9.10.1.2: Liquid Types for Haskell
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Liquid.Measure

Synopsis

Specifications

data Spec lname ty Source #

A generic Spec type, polymorphic over the inner choice of type and binders.

lname corresponds to the names used for entities only known to LH like non-interpreted functions and type aliases.

Constructors

Spec 

Fields

Instances

Instances details
Show BareSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Expand BareSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Expand

Monoid (Spec lname ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Methods

mempty :: Spec lname ty #

mappend :: Spec lname ty -> Spec lname ty -> Spec lname ty #

mconcat :: [Spec lname ty] -> Spec lname ty #

Semigroup (Spec lname ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Methods

(<>) :: Spec lname ty -> Spec lname ty -> Spec lname ty #

sconcat :: NonEmpty (Spec lname ty) -> Spec lname ty #

stimes :: Integral b => b -> Spec lname ty -> Spec lname ty #

(Data lname, Data ty) => Data (Spec lname ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Spec lname ty -> c (Spec lname ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Spec lname ty) #

toConstr :: Spec lname ty -> Constr #

dataTypeOf :: Spec lname ty -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Spec lname ty)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Spec lname ty)) #

gmapT :: (forall b. Data b => b -> b) -> Spec lname ty -> Spec lname ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Spec lname ty -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Spec lname ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Spec lname ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Spec lname ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Spec lname ty -> m (Spec lname ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Spec lname ty -> m (Spec lname ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Spec lname ty -> m (Spec lname ty) #

Generic (Spec lname ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Associated Types

type Rep (Spec lname ty) 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep (Spec lname ty) = D1 ('MetaData "Spec" "Language.Haskell.Liquid.Types.Specs" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "Spec" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "measures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) (Located LHName)]) :*: S1 ('MetaSel ('Just "expSigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(lname, Sort)])) :*: (S1 ('MetaSel ('Just "asmSigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located ty)]) :*: (S1 ('MetaSel ('Just "asmReflectSigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located LHName)]) :*: S1 ('MetaSel ('Just "sigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located (BareTypeV lname))])))) :*: ((S1 ('MetaSel ('Just "invariants") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Maybe LocSymbol, Located ty)]) :*: S1 ('MetaSel ('Just "ialiases") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located ty, Located ty)])) :*: (S1 ('MetaSel ('Just "dataDecls") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [DataDeclP lname ty]) :*: (S1 ('MetaSel ('Just "newtyDecls") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [DataDeclP lname ty]) :*: S1 ('MetaSel ('Just "aliases") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Located (RTAlias Symbol (BareTypeV lname))]))))) :*: (((S1 ('MetaSel ('Just "ealiases") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Located (RTAlias Symbol (ExprV lname))]) :*: S1 ('MetaSel ('Just "embeds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TCEmb (Located LHName)))) :*: (S1 ('MetaSel ('Just "qualifiers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [QualifierV lname]) :*: (S1 ('MetaSel ('Just "lvars") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "lazy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName)))))) :*: ((S1 ('MetaSel ('Just "rewrites") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "rewriteWith") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap (Located LHName) [Located LHName]))) :*: (S1 ('MetaSel ('Just "fails") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: (S1 ('MetaSel ('Just "reflects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "privateReflects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet LocSymbol))))))) :*: ((((S1 ('MetaSel ('Just "opaqueReflects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "autois") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName)))) :*: (S1 ('MetaSel ('Just "hmeas") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: (S1 ('MetaSel ('Just "inlines") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "ignores") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName)))))) :*: ((S1 ('MetaSel ('Just "autosize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "pragmas") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Located String])) :*: (S1 ('MetaSel ('Just "cmeasures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) ()]) :*: (S1 ('MetaSel ('Just "imeasures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) (Located LHName)]) :*: S1 ('MetaSel ('Just "omeasures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) (Located LHName)]))))) :*: (((S1 ('MetaSel ('Just "classes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RClass (Located ty)]) :*: S1 ('MetaSel ('Just "relational") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located LHName, Located (BareTypeV lname), Located (BareTypeV lname), RelExprV lname, RelExprV lname)])) :*: (S1 ('MetaSel ('Just "asmRel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located LHName, Located (BareTypeV lname), Located (BareTypeV lname), RelExprV lname, RelExprV lname)]) :*: (S1 ('MetaSel ('Just "termexprs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, [Located (ExprV lname)])]) :*: S1 ('MetaSel ('Just "rinstance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RInstance (Located ty)])))) :*: ((S1 ('MetaSel ('Just "dvariance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, [Variance])]) :*: (S1 ('MetaSel ('Just "dsize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [([Located ty], lname)]) :*: S1 ('MetaSel ('Just "bounds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RRBEnvV lname (Located ty))))) :*: (S1 ('MetaSel ('Just "axeqs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [EquationV lname]) :*: (S1 ('MetaSel ('Just "defines") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, LMapV lname)]) :*: S1 ('MetaSel ('Just "usedDataCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet LHName)))))))))

Methods

from :: Spec lname ty -> Rep (Spec lname ty) x #

to :: Rep (Spec lname ty) x -> Spec lname ty #

(Show lname, PPrint lname, Show ty, PPrint ty, PPrint (RTypeV lname BTyCon BTyVar (RReftV lname))) => PPrint (Spec lname ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Methods

pprintTidy :: Tidy -> Spec lname ty -> Doc #

pprintPrec :: Int -> Tidy -> Spec lname ty -> Doc #

type Rep (Spec lname ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep (Spec lname ty) = D1 ('MetaData "Spec" "Language.Haskell.Liquid.Types.Specs" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "Spec" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "measures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) (Located LHName)]) :*: S1 ('MetaSel ('Just "expSigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(lname, Sort)])) :*: (S1 ('MetaSel ('Just "asmSigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located ty)]) :*: (S1 ('MetaSel ('Just "asmReflectSigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located LHName)]) :*: S1 ('MetaSel ('Just "sigs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located (BareTypeV lname))])))) :*: ((S1 ('MetaSel ('Just "invariants") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Maybe LocSymbol, Located ty)]) :*: S1 ('MetaSel ('Just "ialiases") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located ty, Located ty)])) :*: (S1 ('MetaSel ('Just "dataDecls") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [DataDeclP lname ty]) :*: (S1 ('MetaSel ('Just "newtyDecls") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [DataDeclP lname ty]) :*: S1 ('MetaSel ('Just "aliases") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Located (RTAlias Symbol (BareTypeV lname))]))))) :*: (((S1 ('MetaSel ('Just "ealiases") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Located (RTAlias Symbol (ExprV lname))]) :*: S1 ('MetaSel ('Just "embeds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TCEmb (Located LHName)))) :*: (S1 ('MetaSel ('Just "qualifiers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [QualifierV lname]) :*: (S1 ('MetaSel ('Just "lvars") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "lazy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName)))))) :*: ((S1 ('MetaSel ('Just "rewrites") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "rewriteWith") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashMap (Located LHName) [Located LHName]))) :*: (S1 ('MetaSel ('Just "fails") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: (S1 ('MetaSel ('Just "reflects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "privateReflects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet LocSymbol))))))) :*: ((((S1 ('MetaSel ('Just "opaqueReflects") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "autois") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName)))) :*: (S1 ('MetaSel ('Just "hmeas") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: (S1 ('MetaSel ('Just "inlines") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "ignores") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName)))))) :*: ((S1 ('MetaSel ('Just "autosize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "pragmas") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Located String])) :*: (S1 ('MetaSel ('Just "cmeasures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) ()]) :*: (S1 ('MetaSel ('Just "imeasures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) (Located LHName)]) :*: S1 ('MetaSel ('Just "omeasures") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MeasureV lname (Located ty) (Located LHName)]))))) :*: (((S1 ('MetaSel ('Just "classes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RClass (Located ty)]) :*: S1 ('MetaSel ('Just "relational") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located LHName, Located (BareTypeV lname), Located (BareTypeV lname), RelExprV lname, RelExprV lname)])) :*: (S1 ('MetaSel ('Just "asmRel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, Located LHName, Located (BareTypeV lname), Located (BareTypeV lname), RelExprV lname, RelExprV lname)]) :*: (S1 ('MetaSel ('Just "termexprs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, [Located (ExprV lname)])]) :*: S1 ('MetaSel ('Just "rinstance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RInstance (Located ty)])))) :*: ((S1 ('MetaSel ('Just "dvariance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, [Variance])]) :*: (S1 ('MetaSel ('Just "dsize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [([Located ty], lname)]) :*: S1 ('MetaSel ('Just "bounds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RRBEnvV lname (Located ty))))) :*: (S1 ('MetaSel ('Just "axeqs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [EquationV lname]) :*: (S1 ('MetaSel ('Just "defines") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Located LHName, LMapV lname)]) :*: S1 ('MetaSel ('Just "usedDataCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet LHName)))))))))

data MSpec ty ctor Source #

Constructors

MSpec 

Fields

Instances

Instances details
Bifunctor MSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

bimap :: (a -> b) -> (c -> d) -> MSpec a c -> MSpec b d #

first :: (a -> b) -> MSpec a c -> MSpec b c #

second :: (b -> c) -> MSpec a b -> MSpec a c #

Functor (MSpec ty) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

fmap :: (a -> b) -> MSpec ty a -> MSpec ty b #

(<$) :: a -> MSpec ty b -> MSpec ty a #

Eq ctor => Monoid (MSpec ty ctor) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

mempty :: MSpec ty ctor #

mappend :: MSpec ty ctor -> MSpec ty ctor -> MSpec ty ctor #

mconcat :: [MSpec ty ctor] -> MSpec ty ctor #

Eq ctor => Semigroup (MSpec ty ctor) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

(<>) :: MSpec ty ctor -> MSpec ty ctor -> MSpec ty ctor #

sconcat :: NonEmpty (MSpec ty ctor) -> MSpec ty ctor #

stimes :: Integral b => b -> MSpec ty ctor -> MSpec ty ctor #

(Data ty, Data ctor) => Data (MSpec ty ctor) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MSpec ty ctor -> c (MSpec ty ctor) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MSpec ty ctor) #

toConstr :: MSpec ty ctor -> Constr #

dataTypeOf :: MSpec ty ctor -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MSpec ty ctor)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MSpec ty ctor)) #

gmapT :: (forall b. Data b => b -> b) -> MSpec ty ctor -> MSpec ty ctor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MSpec ty ctor -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MSpec ty ctor -> r #

gmapQ :: (forall d. Data d => d -> u) -> MSpec ty ctor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MSpec ty ctor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MSpec ty ctor -> m (MSpec ty ctor) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MSpec ty ctor -> m (MSpec ty ctor) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MSpec ty ctor -> m (MSpec ty ctor) #

Generic (MSpec ty ctor) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Associated Types

type Rep (MSpec ty ctor) 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

type Rep (MSpec ty ctor) = D1 ('MetaData "MSpec" "Language.Haskell.Liquid.Types.Types" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "MSpec" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ctorMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap LHName [Def ty ctor])) :*: S1 ('MetaSel ('Just "measMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap (Located LHName) (Measure ty ctor)))) :*: (S1 ('MetaSel ('Just "cmeasMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap (Located LHName) (Measure ty ()))) :*: S1 ('MetaSel ('Just "imeas") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Measure ty ctor]))))

Methods

from :: MSpec ty ctor -> Rep (MSpec ty ctor) x #

to :: Rep (MSpec ty ctor) x -> MSpec ty ctor #

(Show ty, Show ctor, PPrint ctor, PPrint ty) => Show (MSpec ty ctor) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

showsPrec :: Int -> MSpec ty ctor -> ShowS #

show :: MSpec ty ctor -> String #

showList :: [MSpec ty ctor] -> ShowS #

(PPrint t, PPrint a) => PPrint (MSpec t a) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

pprintTidy :: Tidy -> MSpec t a -> Doc #

pprintPrec :: Int -> Tidy -> MSpec t a -> Doc #

type Rep (MSpec ty ctor) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

type Rep (MSpec ty ctor) = D1 ('MetaData "MSpec" "Language.Haskell.Liquid.Types.Types" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "MSpec" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ctorMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap LHName [Def ty ctor])) :*: S1 ('MetaSel ('Just "measMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap (Located LHName) (Measure ty ctor)))) :*: (S1 ('MetaSel ('Just "cmeasMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap (Located LHName) (Measure ty ()))) :*: S1 ('MetaSel ('Just "imeas") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Measure ty ctor]))))

Type Aliases

type BareSpec = Spec Symbol BareType Source #

A BareSpec is the spec we derive by parsing the Liquid Haskell annotations of a single file. As such, it contains things which are relevant for validation and lifting; it contains things like the pragmas the user defined, the termination condition (if termination-checking is enabled) and so on and so forth. Crucially, as a BareSpec is still subject to "preflight checks", it may contain duplicates (e.g. duplicate measures, duplicate type declarations etc.) and therefore most of the fields for a BareSpec are lists, so that we can report these errors to the end user: it would be an error to silently ignore the duplication and leave the duplicate resolution to whichever Eq instance is implemented for the relevant field.

Also, a BareSpec has not yet been subject to name resolution, so it may refer to undefined or out-of-scope entities.

Constructors

mkM :: HasCallStack => Located LHName -> ty -> [DefV v ty bndr] -> MeasureKind -> UnSortedExprs -> MeasureV v ty bndr Source #