unison-parser-typechecker-0.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Unison.PatternMatchCoverage.NormalizedConstraints

Synopsis

Documentation

data NormalizedConstraints vt v loc Source #

Normalized refinement types (fig 6)

Each variable may be associated with a number of constraints represented by VarInfo. A NormalizedConstraints is conceptually the conjunction of all constraints in the map. Disjunction is represented by passing a Set of NormalizedConstraints. So, the constraints are normalized into disjunctive normal form and each NormalizedConstraints is a DNF term.

Additionally, the following invariants are enforced (Section 3.4)

  • Mutual compatibility: No two constraints should conflict with each other.
  • Inhabitation: There must be at least one value that inhabits each refinement type. (N.B. We don't truly know if a type is inhabited, see inhabited in Unison.PatternMatchCoverage.Solve for details. However, the refinement type is inhabited as far as our inhabitation checker is concerned.)

These invariants ensure that each term in our DNF has at least one solution, and it is easy to expand and print these solutions.

Constructors

NormalizedConstraints 

Fields

  • constraintMap :: UFMap v (VarInfo vt v loc)

    Constraints keyed by the variable they constrain. Equality constraints are handled by UFMap.

  • dirtySet :: Set v

    dirty variables are ones that must be checked for inhabitance

Instances

Instances details
(Show v, Show vt) => Show (NormalizedConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

(Var vt, Eq v) => Eq (NormalizedConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

(==) :: NormalizedConstraints vt v loc -> NormalizedConstraints vt v loc -> Bool #

(/=) :: NormalizedConstraints vt v loc -> NormalizedConstraints vt v loc -> Bool #

(Var vt, Ord v) => Ord (NormalizedConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

data VarInfo vt v loc Source #

Normalized constraints on a specific variable

Constructors

VarInfo 

Fields

Instances

Instances details
Generic (VarInfo vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Associated Types

type Rep (VarInfo vt v loc) :: Type -> Type #

Methods

from :: VarInfo vt v loc -> Rep (VarInfo vt v loc) x #

to :: Rep (VarInfo vt v loc) x -> VarInfo vt v loc #

(Show v, Show vt) => Show (VarInfo vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

showsPrec :: Int -> VarInfo vt v loc -> ShowS #

show :: VarInfo vt v loc -> String #

showList :: [VarInfo vt v loc] -> ShowS #

(Var vt, Eq v) => Eq (VarInfo vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

(==) :: VarInfo vt v loc -> VarInfo vt v loc -> Bool #

(/=) :: VarInfo vt v loc -> VarInfo vt v loc -> Bool #

(Var vt, Ord v) => Ord (VarInfo vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

compare :: VarInfo vt v loc -> VarInfo vt v loc -> Ordering #

(<) :: VarInfo vt v loc -> VarInfo vt v loc -> Bool #

(<=) :: VarInfo vt v loc -> VarInfo vt v loc -> Bool #

(>) :: VarInfo vt v loc -> VarInfo vt v loc -> Bool #

(>=) :: VarInfo vt v loc -> VarInfo vt v loc -> Bool #

max :: VarInfo vt v loc -> VarInfo vt v loc -> VarInfo vt v loc #

min :: VarInfo vt v loc -> VarInfo vt v loc -> VarInfo vt v loc #

type Rep (VarInfo vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

type Rep (VarInfo vt v loc) = D1 ('MetaData "VarInfo" "Unison.PatternMatchCoverage.NormalizedConstraints" "unison-parser-typechecker-0.0.0-KNkVGbTXlis2lnVjsRIJUx" 'False) (C1 ('MetaCons "VarInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "vi_id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 v) :*: S1 ('MetaSel ('Just "vi_typ") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type vt loc))) :*: (S1 ('MetaSel ('Just "vi_con") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VarConstraints vt v loc)) :*: S1 ('MetaSel ('Just "vi_eff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EffectInfo))))

data VarConstraints vt v loc Source #

The constraints are different for different types, although most of them take the form of an optional positive constraint and a set of negative constraints.

Constructors

Vc'Constructor (Maybe (ConstructorReference, [(v, Type vt loc)])) (Set ConstructorReference) 
Vc'Effect (Maybe (EffectHandler, [(v, Type vt loc)])) (Set EffectHandler) 
Vc'Boolean (Maybe Bool) (Set Bool) 
Vc'Int (Maybe Int64) (Set Int64) 
Vc'Nat (Maybe Word64) (Set Word64) 
Vc'Float (Maybe Double) (Set Double) 
Vc'Text (Maybe Text) (Set Text) 
Vc'Char (Maybe Char) (Set Char) 
Vc'ListRoot 

Fields

  • (Type vt loc)

    type of list elems

  • (Seq v)

    Positive constraint on cons elements

  • (Seq v)

    Positive constraint on snoc elements

  • IntervalSet

    positive constraint on input list size

Instances

Instances details
Generic (VarConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Associated Types

type Rep (VarConstraints vt v loc) :: Type -> Type #

Methods

from :: VarConstraints vt v loc -> Rep (VarConstraints vt v loc) x #

to :: Rep (VarConstraints vt v loc) x -> VarConstraints vt v loc #

(Show v, Show vt) => Show (VarConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

showsPrec :: Int -> VarConstraints vt v loc -> ShowS #

show :: VarConstraints vt v loc -> String #

showList :: [VarConstraints vt v loc] -> ShowS #

(Var vt, Eq v) => Eq (VarConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

(==) :: VarConstraints vt v loc -> VarConstraints vt v loc -> Bool #

(/=) :: VarConstraints vt v loc -> VarConstraints vt v loc -> Bool #

(Var vt, Ord v) => Ord (VarConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

compare :: VarConstraints vt v loc -> VarConstraints vt v loc -> Ordering #

(<) :: VarConstraints vt v loc -> VarConstraints vt v loc -> Bool #

(<=) :: VarConstraints vt v loc -> VarConstraints vt v loc -> Bool #

(>) :: VarConstraints vt v loc -> VarConstraints vt v loc -> Bool #

(>=) :: VarConstraints vt v loc -> VarConstraints vt v loc -> Bool #

max :: VarConstraints vt v loc -> VarConstraints vt v loc -> VarConstraints vt v loc #

min :: VarConstraints vt v loc -> VarConstraints vt v loc -> VarConstraints vt v loc #

type Rep (VarConstraints vt v loc) Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

type Rep (VarConstraints vt v loc) = D1 ('MetaData "VarConstraints" "Unison.PatternMatchCoverage.NormalizedConstraints" "unison-parser-typechecker-0.0.0-KNkVGbTXlis2lnVjsRIJUx" 'False) (((C1 ('MetaCons "Vc'Constructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ConstructorReference, [(v, Type vt loc)]))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set ConstructorReference))) :+: C1 ('MetaCons "Vc'Effect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (EffectHandler, [(v, Type vt loc)]))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set EffectHandler)))) :+: (C1 ('MetaCons "Vc'Boolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Bool))) :+: C1 ('MetaCons "Vc'Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Int64))))) :+: ((C1 ('MetaCons "Vc'Nat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Word64))) :+: C1 ('MetaCons "Vc'Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Double)))) :+: (C1 ('MetaCons "Vc'Text" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Text))) :+: (C1 ('MetaCons "Vc'Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Char)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Char))) :+: C1 ('MetaCons "Vc'ListRoot" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type vt loc)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq v))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq v)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntervalSet)))))))

markDirty :: Ord v => v -> NormalizedConstraints vt v loc -> NormalizedConstraints vt v loc Source #

Mark a variable as requiring a new test for inhabitation.

updateF Source #

Arguments

:: forall vt v loc f. (Var v, Functor f) 
=> v

variable to lookup

-> (v -> VarInfo vt v loc -> f (ConstraintUpdate (VarInfo vt v loc)))

update function

-> NormalizedConstraints vt v loc

constraint map

-> f (NormalizedConstraints vt v loc) 

Generic function to lookup or alter constraints in the constraint map. Throws an error if the variable is not in the map.

data ConstraintUpdate a Source #

Constructors

Update a 
Ignore 

Instances

Instances details
Functor ConstraintUpdate Source # 
Instance details

Defined in Unison.PatternMatchCoverage.NormalizedConstraints

Methods

fmap :: (a -> b) -> ConstraintUpdate a -> ConstraintUpdate b #

(<$) :: a -> ConstraintUpdate b -> ConstraintUpdate a #

expectCanon :: forall vt v loc. Var v => v -> NormalizedConstraints vt v loc -> (v, VarInfo vt v loc, NormalizedConstraints vt v loc) Source #

Lookup the canonical value of v from the constraint map. Throws an error if the variable is not in the map.

declVar Source #

Arguments

:: forall vt v loc. Var v 
=> v

new variable to install

-> Type vt loc

type of variable

-> (VarInfo vt v loc -> VarInfo vt v loc)

modifier for the default var info of the given type

-> NormalizedConstraints vt v loc

Normalized constraints to install the variable into

-> NormalizedConstraints vt v loc 

Install a new variable into the constraint map. Throws an error if the variable already exists in the map.