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

Safe HaskellNone

Agda.Interaction.BasicOps

Synopsis

Documentation

parseExpr :: Range -> String -> TCM ExprSource

Parses an expression.

giveSource

Arguments

:: InteractionId

Hole.

-> Maybe Range 
-> Expr

The expression to give.

-> TCM Expr

If successful, the very expression is returned unchanged.

Try to fill hole by expression.

Returns the given expression unchanged (for convenient generalization to refine).

refineSource

Arguments

:: InteractionId

Hole.

-> Maybe Range 
-> Expr

The expression to refine the hole with.

-> TCM Expr

The successfully given expression.

Try to refine hole by expression e.

This amounts to successively try to give e, e ?, e ? ?, ... Returns the successfully given expression.

evalInCurrent :: Expr -> TCM ExprSource

Evaluate the given expression in the current environment

data Rewrite Source

Instances

Read Rewrite 

normalForm :: (Normalise a, Simplify a, Reduce a) => Rewrite -> a -> TCMT IO aSource

data OutputForm a b Source

Instances

Reify ProblemConstraint (Closure (OutputForm Expr Expr)) 
Functor (OutputForm a) 
(Show a, Show b) => Show (OutputForm a b) 
(ToConcrete a c, ToConcrete b d) => ToConcrete (OutputForm a b) (OutputForm c d) 

data OutputConstraint' a b Source

A subset of OutputConstraint.

Constructors

OfType' 

Fields

ofName :: b
 
ofExpr :: a
 

getSolvedInteractionPoints :: Bool -> TCM [(InteractionId, MetaId, Expr)]Source

getSolvedInteractionPoints True returns all solutions, even if just solved by another, non-interaction meta.

getSolvedInteractionPoints False only returns metas that are solved by a non-meta.

typeInCurrent :: Rewrite -> Expr -> TCM ExprSource

Returns the type of the expression in the current environment We wake up irrelevant variables just in case the user want to invoke that command in an irrelevant context.

introTactic :: Bool -> InteractionId -> TCM [String]Source

atTopLevel :: TCM a -> TCM aSource

Runs the given computation as if in an anonymous goal at the end of the top-level module.

Sets up current module, scope, and context.

parseName :: Range -> String -> TCM QNameSource

Parse a name.

moduleContentsSource

Arguments

:: Rewrite

How should the types be presented

-> Range

The range of the next argument.

-> String

The module name.

-> TCM ([Name], [(Name, Type)])

Module names, names paired up with corresponding types.

Returns the contents of the given module.