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

Safe HaskellNone
LanguageHaskell98

Agda.TypeChecking.Free

Description

Computing the free variables of a term.

The distinction between rigid and strongly rigid occurrences comes from: Jason C. Reed, PhD thesis, 2009, page 96 (see also his LFMTP 2009 paper)

The main idea is that x = t(x) is unsolvable if x occurs strongly rigidly in t. It might have a solution if the occurrence is not strongly rigid, e.g.

x = f -> suc (f (x ( y -> k))) has x = f -> suc (f (suc k))

Jason C. Reed, PhD thesis, page 106

Under coinductive constructors, occurrences are never strongly rigid. Also, function types and lambdas do not establish strong rigidity. Only inductive constructors do so. (See issue 1271).

Synopsis

Documentation

data FreeVars Source #

Free variables of a term, (disjointly) partitioned into strongly and and weakly rigid variables, flexible variables and irrelevant variables.

Constructors

FV 

Fields

  • stronglyRigidVars :: VarSet

    Variables under only and at least one inductive constructor(s).

  • unguardedVars :: VarSet

    Variables at top or only under inductive record constructors λs and Πs. The purpose of recording these separately is that they can still become strongly rigid if put under a constructor whereas weakly rigid ones stay weakly rigid.

  • weaklyRigidVars :: VarSet

    Ordinary rigid variables, e.g., in arguments of variables.

  • flexibleVars :: IntMap [MetaId]

    Variables occuring in arguments of metas. These are only potentially free, depending how the meta variable is instantiated.

  • irrelevantVars :: VarSet

    Variables in irrelevant arguments and under a DontCare, i.e., in irrelevant positions.

  • unusedVars :: VarSet

    Variables in UnusedArguments.

type Free a = Free' a Any Source #

class Free' a c Source #

Gather free variables in a collection.

Minimal complete definition

freeVars'

Instances

Free' EqualityView c Source # 
Free' ClauseBody c Source # 
Free' Clause c Source # 

Methods

freeVars' :: Clause -> FreeM c Source #

Free' LevelAtom c Source # 
Free' PlusLevel c Source # 
Free' Level c Source # 

Methods

freeVars' :: Level -> FreeM c Source #

Free' Sort c Source # 

Methods

freeVars' :: Sort -> FreeM c Source #

Free' Type c Source # 

Methods

freeVars' :: Type -> FreeM c Source #

Free' Term c Source # 

Methods

freeVars' :: Term -> FreeM c Source #

Free' a c => Free' [a] c Source # 

Methods

freeVars' :: [a] -> FreeM c Source #

Free' a c => Free' (Maybe a) c Source # 

Methods

freeVars' :: Maybe a -> FreeM c Source #

Free' a c => Free' (Dom a) c Source # 

Methods

freeVars' :: Dom a -> FreeM c Source #

Free' a c => Free' (Arg a) c Source # 

Methods

freeVars' :: Arg a -> FreeM c Source #

Free' a c => Free' (Tele a) c Source # 

Methods

freeVars' :: Tele a -> FreeM c Source #

Free' a c => Free' (Abs a) c Source # 

Methods

freeVars' :: Abs a -> FreeM c Source #

Free' a c => Free' (Elim' a) c Source # 

Methods

freeVars' :: Elim' a -> FreeM c Source #

(Free' a c, Free' b c) => Free' (a, b) c Source # 

Methods

freeVars' :: (a, b) -> FreeM c Source #

type FreeVS a = Free' a VarSet Source #

data IgnoreSorts Source #

Where should we skip sorts in free variable analysis?

Constructors

IgnoreNot

Do not skip.

IgnoreInAnnotations

Skip when annotation to a type.

IgnoreAll

Skip unconditionally.

runFree :: (Monoid c, Free' a c) => SingleVar c -> IgnoreSorts -> a -> c Source #

rigidVars :: FreeVars -> VarSet Source #

Rigid variables: either strongly rigid, unguarded, or weakly rigid.

relevantVars :: FreeVars -> VarSet Source #

All but the irrelevant variables.

allVars :: FreeVars -> VarSet Source #

allVars fv includes irrelevant variables.

allFreeVars :: Free' a VarSet => a -> VarSet Source #

Collect all free variables.

allRelevantVars :: Free' a VarSet => a -> VarSet Source #

Collect all relevant free variables.

allRelevantVarsIgnoring :: Free' a VarSet => IgnoreSorts -> a -> VarSet Source #

Collect all relevant free variables, possibly ignoring sorts.

freeIn :: Free a => Nat -> a -> Bool Source #

isBinderUsed :: Free a => Abs a -> Bool Source #

Is the variable bound by the abstraction actually used?

relevantIn :: Free a => Nat -> a -> Bool Source #

data Occurrence Source #

Constructors

NoOccurrence 
Irrelevantly 
StronglyRigid

Under at least one and only inductive constructors.

Unguarded

In top position, or only under inductive record constructors.

WeaklyRigid

In arguments to variables and definitions.

Flexible [MetaId]

In arguments of metas.

Unused 

occurrence :: FreeV a => Nat -> a -> Occurrence Source #

Compute an occurrence of a single variable in a piece of internal syntax.

closed :: Free' a All => a -> Bool Source #

Is the term entirely closed (no free variables)?

freeVars :: (Monoid c, Singleton Variable c, Free' a c) => a -> c Source #

Doesn't go inside solved metas, but collects the variables from a metavariable application X ts as flexibleVars.