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

Safe HaskellNone
LanguageHaskell98

Agda.TypeChecking.Forcing

Description

A constructor argument is forced if it appears as pattern variable in an index of the target.

For instance x is forced in sing and n is forced in zero and suc:

  data Sing {a}{A : Set a} : A -> Set where
    sing : (x : A) -> Sing x

  data Fin : Nat -> Set where
    zero : (n : Nat) -> Fin (suc n)
    suc  : (n : Nat) (i : Fin n) -> Fin (suc n)

At runtime, forced constructor arguments may be erased as they can be recovered from dot patterns. In the epic backend, unsing : {A : Set} (x : A) -> Sing x -> A unsing .x (sing x) = x becomes unsing x sing = x and proj : (n : Nat) (i : Fin n) -> Nat proj .(suc n) (zero n) = n proj .(suc n) (suc n i) = n becomes proj (suc n) zero = n proj (suc n) (suc i) = n

Forcing is a concept from pattern matching and thus builds on the concept of equality (I) used there (closed terms, extensional) which is different from the equality (II) used in conversion checking and the constraint solver (open terms, intensional).

Up to issue 1441 (Feb 2015), the forcing analysis here relied on the wrong equality (II), considering type constructors as injective. This is unsound for Epic's program extraction, but ok if forcing is only used to decide which arguments to skip during conversion checking.

From now on, forcing uses equality (I) and does not search for forced variables under type constructors. This may lose some savings during conversion checking. If this turns out to be a problem, the old forcing could be brought back, using a new modality Skip to indicate that this is a relevant argument but still can be skipped during conversion checking as it is forced by equality (II).

Synopsis

Documentation

addForcingAnnotations :: Type -> TCM Type Source

Given the type of a constructor (excluding the parameters), decide which arguments are forced. Update the relevance info in the domains accordingly. Precondition: the type is of the form Γ → D vs and the vs are in normal form.

class ForcedVariables a where Source

Compute the pattern variables of a term or term-like thing.

Methods

forcedVariables :: a -> [Nat] Source

Instances

ForcedVariables Term Source

Assumes that the term is in normal form.

(ForcedVariables a, Foldable t) => ForcedVariables (t a) Source 

force :: Sort -> [Nat] -> Type -> TCM Type Source

force s xs t marks the domains xs in function type t as forced. Domains bigger than s are marked as Forced Big, others as Forced Small. Counting left-to-right, starting with 0. Precondition: function type is exposed.