Agda-2.5.1.2: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.TypeChecking.Rules.LHS.Problem

Synopsis

Documentation

data FlexibleVarKind Source #

When we encounter a flexible variable in the unifier, where did it come from? The alternatives are ordered such that we will assign the higher one first, i.e., first we try to assign a DotFlex, then...

Constructors

RecordFlex [FlexibleVarKind]

From a record pattern (ConP). Saves the FlexibleVarKind of its subpatterns.

ImplicitFlex

From a hidden formal argument or underscore (WildP).

DotFlex

From a dot pattern (DotP).

data FlexibleVar a Source #

Flexible variables are equipped with information where they come from, in order to make a choice which one to assign when two flexibles are unified.

Constructors

FlexibleVar 

Instances

Functor FlexibleVar Source # 

Methods

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

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

Foldable FlexibleVar Source # 

Methods

fold :: Monoid m => FlexibleVar m -> m #

foldMap :: Monoid m => (a -> m) -> FlexibleVar a -> m #

foldr :: (a -> b -> b) -> b -> FlexibleVar a -> b #

foldr' :: (a -> b -> b) -> b -> FlexibleVar a -> b #

foldl :: (b -> a -> b) -> b -> FlexibleVar a -> b #

foldl' :: (b -> a -> b) -> b -> FlexibleVar a -> b #

foldr1 :: (a -> a -> a) -> FlexibleVar a -> a #

foldl1 :: (a -> a -> a) -> FlexibleVar a -> a #

toList :: FlexibleVar a -> [a] #

null :: FlexibleVar a -> Bool #

length :: FlexibleVar a -> Int #

elem :: Eq a => a -> FlexibleVar a -> Bool #

maximum :: Ord a => FlexibleVar a -> a #

minimum :: Ord a => FlexibleVar a -> a #

sum :: Num a => FlexibleVar a -> a #

product :: Num a => FlexibleVar a -> a #

Traversable FlexibleVar Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FlexibleVar a -> f (FlexibleVar b) #

sequenceA :: Applicative f => FlexibleVar (f a) -> f (FlexibleVar a) #

mapM :: Monad m => (a -> m b) -> FlexibleVar a -> m (FlexibleVar b) #

sequence :: Monad m => FlexibleVar (m a) -> m (FlexibleVar a) #

Eq a => Eq (FlexibleVar a) Source # 
Show a => Show (FlexibleVar a) Source # 
LensHiding (FlexibleVar a) Source # 
ChooseFlex a => ChooseFlex (FlexibleVar a) Source # 

data Problem' p Source #

State of typechecking a LHS; input to split. [Ulf Norell's PhD, page. 35]

In Problem ps p delta, ps are the user patterns of supposed type delta. p is the pattern resulting from the splitting.

Constructors

Problem 

Fields

type Problem = Problem' [NamedArg DeBruijnPattern] Source #

The de Bruijn indices in the pattern refer to positions in the list of abstract patterns in the problem, counted from the back.

data ProblemRest Source #

User patterns that could not be given a type yet.

Example: f : (b : Bool) -> if b then Nat else Nat -> Nat f true = zero f false zero = zero f false (suc n) = n In this sitation, for clause 2, we construct an initial problem problemInPat = [false] problemTel = (b : Bool) problemRest.restPats = [zero] problemRest.restType = if b then Nat else Nat -> Nat As we instantiate b to false, the restType reduces to Nat -> Nat and we can move pattern zero over to problemInPat.

Constructors

ProblemRest 

Fields

data Focus Source #

Constructors

Focus 

Fields

LitFocus Literal [NamedArg DeBruijnPattern] Type 

data SplitProblem Source #

Result of splitProblem: Determines position for the next split.

Constructors

Split

Split on constructor pattern.

Fields

SplitRest

Split on projection pattern.

Fields

consSplitProblem Source #

Arguments

:: NamedArg Pattern

p A pattern.

-> ArgName

x The name of the argument (from its type).

-> Dom Type

t Its type.

-> SplitProblem

The split problem, containing splitLPats ps;xs:ts.

-> SplitProblem

The result, now containing splitLPats (p,ps);(x,xs):(t,ts).

Put a typed pattern on the very left of a SplitProblem.

data DotPatternInst Source #

Instantiations of a dot pattern with a term. `Maybe e` if the user wrote a dot pattern .e Nothing if this is an instantiation of an implicit argument or an underscore _

data LHSState Source #

State worked on during the main loop of checking a lhs.