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

Safe HaskellNone
LanguageHaskell2010

Agda.TypeChecking.Rules.LHS

Synopsis

Documentation

checkLeftHandSide Source #

Arguments

:: Call

Trace, e.g. CheckPatternShadowing clause

-> Maybe QName

The name of the definition we are checking.

-> [NamedArg Pattern]

The patterns.

-> Type

The expected type a = Γ → b.

-> Maybe Substitution

Module parameter substitution from with-abstraction.

-> [ProblemEq]

Patterns that have been stripped away by with-desugaring. ^ These should not contain any proper matches.

-> (LHSResult -> TCM a)

Continuation.

-> TCM a 

Check a LHS. Main function.

checkLeftHandSide a ps a ret checks that user patterns ps eliminate the type a of the defined function, and calls continuation ret if successful.

data LHSResult Source #

Result of checking the LHS of a clause.

Constructors

LHSResult 

Fields

  • lhsParameters :: Nat

    The number of original module parameters. These are present in the the patterns.

  • lhsVarTele :: Telescope

    Δ : The types of the pattern variables, in internal dependency order. Corresponds to clauseTel.

  • lhsPatterns :: [NamedArg DeBruijnPattern]

    The patterns in internal syntax.

  • lhsHasAbsurd :: Bool

    Whether the LHS has at least one absurd pattern.

  • lhsBodyType :: Arg Type

    The type of the body. Is if Γ is defined. Irrelevant to indicate the rhs must be checked in irrelevant mode.

  • lhsPatSubst :: Substitution

    Substitution version of lhsPatterns, only up to the first projection pattern. Δ |- lhsPatSubst : Γ. Where Γ is the argument telescope of the function. This is used to update inherited dot patterns in with-function clauses.

  • lhsAsBindings :: [AsBinding]

    As-bindings from the left-hand side. Return instead of bound since we want them in where's and right-hand sides, but not in with-clauses (Issue 2303).

bindAsPatterns :: [AsBinding] -> TCM a -> TCM a Source #

Bind as patterns

class IsFlexiblePattern a where Source #

A pattern is flexible if it is dotted or implicit, or a record pattern with only flexible subpatterns.

Minimal complete definition

maybeFlexiblePattern

checkSortOfSplitVar :: (MonadTCM tcm, MonadError TCErr tcm, LensSort a) => a -> tcm () Source #