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

Language.Haskell.Liquid.Types.Specs

Description

This module contains the top-level structures that hold information about specifications.

Synopsis

Different types of specifications

There are different types or "flavours" for a specification, depending on its lifecycle. The main goal is always the same, i.e. refining the Haskell types and produce a final statement (i.e. safe or unsafe) about the input program. In order to do so, a specification is transformed in the way described by this picture:

    +---------------+                                +-------------------+
    |   BareSpec    |                                |                   |  checked by liquid/liquidOne
    |               |                    ------------|    TargetSpec     |----------------------------- ..
    |(input module) |                   /            |                   |
    +---------------+  makeTargetSpec  /             +-------------------+
           +         -----------------/
    +---------------+                 \              +-------------------+
    | {LiftedSpec}  |                  \             |                   |    serialised on disk
    |               |                   -------------|    LiftedSpec     |----------------------------- ..
    |(dependencies) |                                |                   |
    +---------------+                                +-------------------+
          ^                                                    |
          |                   used-as                          |
          +----------------------------------------------------+

More specifically, we distinguish:

  • BareSpec - is the specification obtained by parsing the Liquid annotations of the input Haskell file. It typically contains information about the associated input Haskell module, with the exceptions of assumptions that can refer to functions defined in other modules.
  • LiftedSpec - is the specification we obtain by "lifting" the BareSpec. Most importantly, a LiftedSpec gets serialised on disk and becomes a dependency for the verification of other BareSpecs.

Lifting in this context consist of:

  1. Perform name-resolution (e.g. make all the relevant GHC's Vars qualified, resolve GHC's Names, etc);
  2. Strip the final LiftedSpec with information which are relevant (read: local) to just the input BareSpec. An example would be local signatures, used to annotate internal, auxiliary functions within a Module;
  3. Strip termination checks, which are required (if specified) for a BareSpec but not for the LiftedSpec.
  • TargetSpec - is the specification we actually use for refinement, and is conceptually an "augmented" BareSpec. You can create a TargetSpec by calling makeTargetSpec.

In order to produce these spec types we have to gather information about the module being compiled by using the GHC API and retain enough context of the compiled Module in order to be able to construct the types introduced aboves. The rest of this module introduced also these intermediate structures.

The following is the overall type for specifications obtained from parsing the target source and dependent libraries. IMPORTANT: A TargetInfo is what is checked by LH itself and it NEVER contains the LiftedSpec, because the checking happens only on the BareSpec of the target module.

data TargetInfo Source #

Constructors

TargetInfo 

Fields

Gathering information about a module

data TargetSrc Source #

The TargetSrc type is a collection of all the things we know about a module being currently checked. It include things like the name of the module, the list of CoreBinds, the TyCons declared in this module (that includes TyCons for classes), typeclass instances and so and so forth. It might be consider a sort of ModGuts embellished with LH-specific information (for example, giDefVars are populated with datacons from the module plus the let vars derived from the A-normalisation).

Constructors

TargetSrc 

Fields

TargetSpec

 

data TargetSpec Source #

A TargetSpec is what we actually check via LiquidHaskell. It is created as part of mkTargetSpec alongside the LiftedSpec. It shares a similar structure with a BareSpec, but manipulates and transforms the data in preparation to the checking process.

Constructors

TargetSpec 

Instances

Instances details
Show TargetSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

PPrint TargetSpec Source #

Pretty Printing -----------------------------------------------------------

Instance details

Defined in Language.Haskell.Liquid.GHC.Interface

HasConfig TargetSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

BareSpec

 

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.

LiftedSpec

 

data LiftedSpec Source #

A LiftedSpec is derived from an input BareSpec and a set of its dependencies. The general motivations for lifting a spec are (a) name resolution, (b) the fact that some info is only relevant for checking the body of functions but does not need to be exported, e.g. termination measures, or the fact that a type signature was assumed. A LiftedSpec is what we serialise on disk and what the clients should will be using.

What we do not have compared to a BareSpec:

  • The reflSigs, they are now just "normal" signatures;
  • The lazy, we don't do termination checking in lifted specs;
  • The reflects, the reflection has already happened at this point;
  • The hmeas, we have already turned these into measures at this point;
  • The inlines, ditto as hmeas;
  • The ignores, ditto as hmeas;
  • The pragmas, we can't make any use of this information for lifted specs;
  • The termexprs, we don't do termination checking in lifted specs;

Apart from less fields, a LiftedSpec replaces all instances of lists with sets, to enforce duplicate detection and removal on what we serialise on disk.

Constructors

LiftedSpec 

Fields

Instances

Instances details
Binary LiftedSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Data LiftedSpec 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) -> LiftedSpec -> c LiftedSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LiftedSpec #

toConstr :: LiftedSpec -> Constr #

dataTypeOf :: LiftedSpec -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> LiftedSpec -> LiftedSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LiftedSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LiftedSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> LiftedSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LiftedSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LiftedSpec -> m LiftedSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LiftedSpec -> m LiftedSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LiftedSpec -> m LiftedSpec #

Generic LiftedSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Associated Types

type Rep LiftedSpec 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep LiftedSpec = D1 ('MetaData "LiftedSpec" "Language.Haskell.Liquid.Types.Specs" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "LiftedSpec" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "liftedMeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Symbol (MeasureV LHName LocBareTypeLHName (Located LHName)))) :*: (S1 ('MetaSel ('Just "liftedExpSigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (LHName, Sort))) :*: S1 ('MetaSel ('Just "liftedPrivateReflects") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet LocSymbol)))) :*: (S1 ('MetaSel ('Just "liftedAsmSigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName, LocBareTypeLHName))) :*: (S1 ('MetaSel ('Just "liftedSigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName, LocBareTypeLHName))) :*: S1 ('MetaSel ('Just "liftedInvariants") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Maybe LocSymbol, LocBareTypeLHName)))))) :*: ((S1 ('MetaSel ('Just "liftedIaliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (LocBareTypeLHName, LocBareTypeLHName))) :*: (S1 ('MetaSel ('Just "liftedDataDecls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet DataDeclLHName)) :*: S1 ('MetaSel ('Just "liftedNewtyDecls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet DataDeclLHName)))) :*: ((S1 ('MetaSel ('Just "liftedAliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located (RTAlias Symbol BareTypeLHName)))) :*: S1 ('MetaSel ('Just "liftedEaliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located (RTAlias Symbol (ExprV LHName)))))) :*: (S1 ('MetaSel ('Just "liftedEmbeds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TCEmb (Located LHName))) :*: S1 ('MetaSel ('Just "liftedQualifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (QualifierV LHName))))))) :*: (((S1 ('MetaSel ('Just "liftedLvars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName))) :*: (S1 ('MetaSel ('Just "liftedAutois") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "liftedAutosize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName))))) :*: ((S1 ('MetaSel ('Just "liftedCmeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Symbol (MeasureV LHName LocBareTypeLHName ()))) :*: S1 ('MetaSel ('Just "liftedImeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (MeasureV LHName LocBareTypeLHName (Located LHName))))) :*: (S1 ('MetaSel ('Just "liftedOmeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (MeasureV LHName LocBareTypeLHName (Located LHName)))) :*: S1 ('MetaSel ('Just "liftedClasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (RClass LocBareTypeLHName)))))) :*: ((S1 ('MetaSel ('Just "liftedRinstance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (RInstance LocBareTypeLHName))) :*: (S1 ('MetaSel ('Just "liftedDsize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [([LocBareTypeLHName], LHName)]) :*: S1 ('MetaSel ('Just "liftedDvariance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName, [Variance]))))) :*: ((S1 ('MetaSel ('Just "liftedBounds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RRBEnvV LHName LocBareTypeLHName)) :*: S1 ('MetaSel ('Just "liftedAxeqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (EquationV LHName)))) :*: (S1 ('MetaSel ('Just "liftedDefines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Symbol (LMapV LHName))) :*: S1 ('MetaSel ('Just "liftedUsedDataCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet LHName))))))))
Show LiftedSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Eq LiftedSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Hashable LiftedSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep LiftedSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep LiftedSpec = D1 ('MetaData "LiftedSpec" "Language.Haskell.Liquid.Types.Specs" "liquidhaskell-boot-0.9.10.1.2-inplace" 'False) (C1 ('MetaCons "LiftedSpec" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "liftedMeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Symbol (MeasureV LHName LocBareTypeLHName (Located LHName)))) :*: (S1 ('MetaSel ('Just "liftedExpSigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (LHName, Sort))) :*: S1 ('MetaSel ('Just "liftedPrivateReflects") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet LocSymbol)))) :*: (S1 ('MetaSel ('Just "liftedAsmSigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName, LocBareTypeLHName))) :*: (S1 ('MetaSel ('Just "liftedSigs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName, LocBareTypeLHName))) :*: S1 ('MetaSel ('Just "liftedInvariants") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Maybe LocSymbol, LocBareTypeLHName)))))) :*: ((S1 ('MetaSel ('Just "liftedIaliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (LocBareTypeLHName, LocBareTypeLHName))) :*: (S1 ('MetaSel ('Just "liftedDataDecls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet DataDeclLHName)) :*: S1 ('MetaSel ('Just "liftedNewtyDecls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet DataDeclLHName)))) :*: ((S1 ('MetaSel ('Just "liftedAliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located (RTAlias Symbol BareTypeLHName)))) :*: S1 ('MetaSel ('Just "liftedEaliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located (RTAlias Symbol (ExprV LHName)))))) :*: (S1 ('MetaSel ('Just "liftedEmbeds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TCEmb (Located LHName))) :*: S1 ('MetaSel ('Just "liftedQualifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (QualifierV LHName))))))) :*: (((S1 ('MetaSel ('Just "liftedLvars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName))) :*: (S1 ('MetaSel ('Just "liftedAutois") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName))) :*: S1 ('MetaSel ('Just "liftedAutosize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName))))) :*: ((S1 ('MetaSel ('Just "liftedCmeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Symbol (MeasureV LHName LocBareTypeLHName ()))) :*: S1 ('MetaSel ('Just "liftedImeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (MeasureV LHName LocBareTypeLHName (Located LHName))))) :*: (S1 ('MetaSel ('Just "liftedOmeasures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (MeasureV LHName LocBareTypeLHName (Located LHName)))) :*: S1 ('MetaSel ('Just "liftedClasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (RClass LocBareTypeLHName)))))) :*: ((S1 ('MetaSel ('Just "liftedRinstance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (RInstance LocBareTypeLHName))) :*: (S1 ('MetaSel ('Just "liftedDsize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [([LocBareTypeLHName], LHName)]) :*: S1 ('MetaSel ('Just "liftedDvariance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Located LHName, [Variance]))))) :*: ((S1 ('MetaSel ('Just "liftedBounds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RRBEnvV LHName LocBareTypeLHName)) :*: S1 ('MetaSel ('Just "liftedAxeqs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (EquationV LHName)))) :*: (S1 ('MetaSel ('Just "liftedDefines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Symbol (LMapV LHName))) :*: S1 ('MetaSel ('Just "liftedUsedDataCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet LHName))))))))

Tracking dependencies

 

newtype TargetDependencies Source #

The target dependencies that concur to the creation of a TargetSpec and a LiftedSpec.

Instances

Instances details
Binary TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Monoid TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Semigroup TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Data TargetDependencies 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) -> TargetDependencies -> c TargetDependencies #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TargetDependencies #

toConstr :: TargetDependencies -> Constr #

dataTypeOf :: TargetDependencies -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> TargetDependencies -> TargetDependencies #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TargetDependencies -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TargetDependencies -> r #

gmapQ :: (forall d. Data d => d -> u) -> TargetDependencies -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TargetDependencies -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TargetDependencies -> m TargetDependencies #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetDependencies -> m TargetDependencies #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TargetDependencies -> m TargetDependencies #

Generic TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Associated Types

type Rep TargetDependencies 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep TargetDependencies = D1 ('MetaData "TargetDependencies" "Language.Haskell.Liquid.Types.Specs" "liquidhaskell-boot-0.9.10.1.2-inplace" 'True) (C1 ('MetaCons "TargetDependencies" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap StableModule LiftedSpec))))
Show TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Eq TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep TargetDependencies Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

type Rep TargetDependencies = D1 ('MetaData "TargetDependencies" "Language.Haskell.Liquid.Types.Specs" "liquidhaskell-boot-0.9.10.1.2-inplace" 'True) (C1 ('MetaCons "TargetDependencies" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDependencies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap StableModule LiftedSpec))))

Predicates on spec types

 

isPLEVar :: TargetSpec -> Var -> Bool Source #

Returns True if the input Var is a PLE one.

isExportedVar :: TargetSrc -> Var -> Bool Source #

Returns True if the input Var was exported in the module the input TargetSrc represents.

Other types

data QImports Source #

QImports is a map of qualified imports.

Constructors

QImports 

Fields

Instances

Instances details
Show QImports Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

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 GhcSpecVars Source #

The collection of GHC Vars that a TargetSpec needs to verify (or skip).

Constructors

SpVar 

Fields

data GhcSpecSig Source #

Constructors

SpSig 

Fields

data GhcSpecNames Source #

Constructors

SpNames 

Fields

Instances

Instances details
Show GhcSpecNames Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

data GhcSpecTerm Source #

Constructors

SpTerm 

Fields

data GhcSpecRefl Source #

Constructors

SpRefl 

Fields

data GhcSpecData Source #

Constructors

SpData 

Fields

Instances

Instances details
Show GhcSpecData Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

data GhcSpecQual Source #

Constructors

SpQual 

Fields

Instances

Instances details
Show GhcSpecQual Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

emapSpecM Source #

Arguments

:: Monad m 
=> Bool

The bscope setting, which affects which names are considered to be in scope in refinment types.

-> (LHName -> [Symbol])

For names that have a local environment return the names in scope.

-> ([Symbol] -> lname0 -> m lname1)

The first parameter of the function argument are the variables in scope.

-> ([Symbol] -> ty0 -> m ty1) 
-> Spec lname0 ty0 
-> m (Spec lname1 ty1) 

A function to resolve names in the ty parameter of Spec

mapSpecLName :: (lname0 -> lname1) -> Spec lname0 ty -> Spec lname1 ty Source #

mapSpecTy :: (ty0 -> ty1) -> Spec lname ty0 -> Spec lname ty1 Source #

Legacy data structures

 

data GhcSrc Source #

Constructors

Src 

Fields

data GhcSpec Source #

Constructors

SP 

Fields

Instances

Instances details
HasConfig GhcSpec Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Specs

Provisional compatibility exports & optics

Orphan instances

Show TyConMap Source # 
Instance details