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

Safe HaskellNone
LanguageHaskell2010

Agda.Interaction.InteractionTop

Contents

Synopsis

Documentation

showOpenMetas :: TCM [String] Source #

Print open metas nicely.

type Parse a = ExceptT String (StateT String Identity) a Source #

The Parse monad. StateT state holds the remaining input.

data Remove Source #

Used to indicate whether something should be removed or not.

Constructors

Remove 
Keep 

data IOTCM' range Source #

Instances
Functor IOTCM' Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

fmap :: (a -> b) -> IOTCM' a -> IOTCM' b #

(<$) :: a -> IOTCM' b -> IOTCM' a #

Foldable IOTCM' Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

fold :: Monoid m => IOTCM' m -> m #

foldMap :: Monoid m => (a -> m) -> IOTCM' a -> m #

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

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

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

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

foldr1 :: (a -> a -> a) -> IOTCM' a -> a #

foldl1 :: (a -> a -> a) -> IOTCM' a -> a #

toList :: IOTCM' a -> [a] #

null :: IOTCM' a -> Bool #

length :: IOTCM' a -> Int #

elem :: Eq a => a -> IOTCM' a -> Bool #

maximum :: Ord a => IOTCM' a -> a #

minimum :: Ord a => IOTCM' a -> a #

sum :: Num a => IOTCM' a -> a #

product :: Num a => IOTCM' a -> a #

Traversable IOTCM' Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

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

sequenceA :: Applicative f => IOTCM' (f a) -> f (IOTCM' a) #

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

sequence :: Monad m => IOTCM' (m a) -> m (IOTCM' a) #

Read range => Read (IOTCM' range) Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

readsPrec :: Int -> ReadS (IOTCM' range) #

readList :: ReadS [IOTCM' range] #

readPrec :: ReadPrec (IOTCM' range) #

readListPrec :: ReadPrec [IOTCM' range] #

Show range => Show (IOTCM' range) Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

showsPrec :: Int -> IOTCM' range -> ShowS #

show :: IOTCM' range -> String #

showList :: [IOTCM' range] -> ShowS #

data Interaction' range Source #

Constructors

Cmd_load FilePath [String]

cmd_load m argv loads the module in file m, using argv as the command-line options.

Cmd_compile CompilerBackend FilePath [String]

cmd_compile b m argv compiles the module in file m using the backend b, using argv as the command-line options.

Cmd_constraints 
Cmd_metas

Show unsolved metas. If there are no unsolved metas but unsolved constraints show those instead.

Cmd_show_module_contents_toplevel Rewrite String

Shows all the top-level names in the given module, along with their types. Uses the top-level scope.

Cmd_search_about_toplevel Rewrite String

Shows all the top-level names in scope which mention all the given identifiers in their type.

Cmd_solveAll Rewrite

Solve (all goals / the goal at point) whose values are determined by the constraints.

Cmd_solveOne Rewrite InteractionId range String 
Cmd_autoOne InteractionId range String

Solve (all goals / the goal at point) by using Auto.

Cmd_autoAll 
Cmd_infer_toplevel Rewrite String

Parse the given expression (as if it were defined at the top-level of the current module) and infer its type.

Cmd_compute_toplevel ComputeMode String

Parse and type check the given expression (as if it were defined at the top-level of the current module) and normalise it.

Cmd_load_highlighting_info FilePath

cmd_load_highlighting_info source loads syntax highlighting information for the module in source, and asks Emacs to apply highlighting info from this file.

If the module does not exist, or its module name is malformed or cannot be determined, or the module has not already been visited, or the cached info is out of date, then no highlighting information is printed.

This command is used to load syntax highlighting information when a new file is opened, and it would probably be annoying if jumping to the definition of an identifier reset the proof state, so this command tries not to do that. One result of this is that the command uses the current include directories, whatever they happen to be.

Cmd_tokenHighlighting FilePath Remove

Tells Agda to compute token-based highlighting information for the file.

This command works even if the file's module name does not match its location in the file system, or if the file is not scope-correct. Furthermore no file names are put in the generated output. Thus it is fine to put source code into a temporary file before calling this command. However, the file extension should be correct.

If the second argument is Remove, then the (presumably temporary) file is removed after it has been read.

Cmd_highlight InteractionId range String

Tells Agda to compute highlighting information for the expression just spliced into an interaction point.

ShowImplicitArgs Bool

Tells Agda whether or not to show implicit arguments.

ToggleImplicitArgs

Toggle display of implicit arguments.

Cmd_give UseForce InteractionId range String

Goal commands

If the range is noRange, then the string comes from the minibuffer rather than the goal.

Cmd_refine InteractionId range String 
Cmd_intro Bool InteractionId range String 
Cmd_refine_or_intro Bool InteractionId range String 
Cmd_context Rewrite InteractionId range String 
Cmd_helper_function Rewrite InteractionId range String 
Cmd_infer Rewrite InteractionId range String 
Cmd_goal_type Rewrite InteractionId range String 
Cmd_elaborate_give Rewrite InteractionId range String

Grabs the current goal's type and checks the expression in the hole against it. Returns the elaborated term.

Cmd_goal_type_context Rewrite InteractionId range String

Displays the current goal and context.

Cmd_goal_type_context_infer Rewrite InteractionId range String

Displays the current goal and context and infers the type of an expression.

Cmd_goal_type_context_check Rewrite InteractionId range String

Grabs the current goal's type and checks the expression in the hole against it.

Cmd_show_module_contents Rewrite InteractionId range String

Shows all the top-level names in the given module, along with their types. Uses the scope of the given goal.

Cmd_make_case InteractionId range String 
Cmd_compute ComputeMode InteractionId range String 
Cmd_why_in_scope InteractionId range String 
Cmd_why_in_scope_toplevel String 
Cmd_show_version

Displays version of the running Agda

Cmd_abort

Abort the current computation.

Does nothing if no computation is in progress.

Instances
Functor Interaction' Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

fmap :: (a -> b) -> Interaction' a -> Interaction' b #

(<$) :: a -> Interaction' b -> Interaction' a #

Foldable Interaction' Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

fold :: Monoid m => Interaction' m -> m #

foldMap :: Monoid m => (a -> m) -> Interaction' a -> m #

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

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

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

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

foldr1 :: (a -> a -> a) -> Interaction' a -> a #

foldl1 :: (a -> a -> a) -> Interaction' a -> a #

toList :: Interaction' a -> [a] #

null :: Interaction' a -> Bool #

length :: Interaction' a -> Int #

elem :: Eq a => a -> Interaction' a -> Bool #

maximum :: Ord a => Interaction' a -> a #

minimum :: Ord a => Interaction' a -> a #

sum :: Num a => Interaction' a -> a #

product :: Num a => Interaction' a -> a #

Traversable Interaction' Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

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

sequenceA :: Applicative f => Interaction' (f a) -> f (Interaction' a) #

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

sequence :: Monad m => Interaction' (m a) -> m (Interaction' a) #

Read range => Read (Interaction' range) Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Show range => Show (Interaction' range) Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

showsPrec :: Int -> Interaction' range -> ShowS #

show :: Interaction' range -> String #

showList :: [Interaction' range] -> ShowS #

type Interaction = Interaction' Range Source #

An interactive computation.

data CommandQueue Source #

Command queues.

Constructors

CommandQueue 

Fields

  • commands :: !(TChan (Integer, Command))

    Commands that should be processed, in the order in which they should be processed. Each command is associated with a number, and the numbers are strictly increasing. Abort commands are not put on this queue.

  • abort :: !(TVar (Maybe Integer))

    When this variable is set to Just n an attempt is made to abort all commands with a command number that is at most n.

type Command = Command' IOTCM Source #

IOTCM commands.

data Command' a Source #

A generalised command type.

Constructors

Command !a

A command.

Done

Stop processing commands.

Error String

An error message for a command that could not be parsed.

Instances
Show a => Show (Command' a) Source # 
Instance details

Defined in Agda.Interaction.InteractionTop

Methods

showsPrec :: Int -> Command' a -> ShowS #

show :: Command' a -> String #

showList :: [Command' a] -> ShowS #

type CommandM = StateT CommandState TCM Source #

Monad for computing answers to interactive commands.

CommandM is TCMT extended with state CommandState.

data CommandState Source #

Auxiliary state of an interactive computation.

Constructors

CommandState 

Fields

initCommandState :: CommandQueue -> CommandState Source #

Initial auxiliary interaction state

liftLocalState :: TCM a -> CommandM a Source #

Restore TCState, do not touch CommandState.

revLift Source #

Arguments

:: MonadState st m 
=> (forall c. m c -> st -> k (c, st))

run

-> (forall b. k b -> m b)

lift

-> (forall x. (m a -> k x) -> k x) 
-> m a

reverse lift in double negative position

Build an opposite action to lift for state monads.

revLiftTC Source #

Arguments

:: MonadTCState m 
=> (forall c. m c -> TCState -> k (c, TCState))

run

-> (forall b. k b -> m b)

lift

-> (forall x. (m a -> k x) -> k x) 
-> m a

reverse lift in double negative position

commandMToIO :: (forall x. (CommandM a -> IO x) -> IO x) -> CommandM a Source #

Opposite of liftIO for CommandM. Use only if main errors are already catched.

liftCommandMT :: (forall a. TCM a -> TCM a) -> CommandM a -> CommandM a Source #

Lift a TCM action transformer to a CommandM action transformer.

liftCommandMTLocalState :: (forall a. TCM a -> TCM a) -> CommandM a -> CommandM a Source #

Ditto, but restore state.

putResponse :: Response -> CommandM () Source #

Put a response by the callback function given by stInteractionOutputCallback.

handleCommand_ :: CommandM () -> CommandM () Source #

Do setup and error handling for a command.

handleCommand :: (forall a. CommandM a -> CommandM a) -> CommandM () -> CommandM () -> CommandM () Source #

runInteraction :: IOTCM -> CommandM () Source #

Run an IOTCM value, catch the exceptions, emit output

If an error happens the state of CommandM does not change, but stPersistent may change (which contains successfully loaded interfaces for example).

maybeAbort :: (IOTCM -> CommandM a) -> CommandM (Command' (Maybe a)) Source #

If the next command from the command queue is anything but an actual command, then the command is returned.

If the command is an IOTCM command, then the following happens: The given computation is applied to the command and executed. If an abort command is encountered (and acted upon), then the computation is interrupted, the persistent state and all options are restored, and some commands are sent to the frontend. If the computation was not interrupted, then its result is returned.

initialiseCommandQueue Source #

Arguments

:: IO Command

Returns the next command.

-> IO CommandQueue 

Creates a command queue, and forks a thread that writes commands to the queue. The queue is returned.

readsToParse :: String -> (String -> Maybe (a, String)) -> Parse a Source #

Converter from the type of reads to Parse The first paramter is part of the error message in case the parse fails.

exact :: String -> Parse () Source #

Demand an exact string.

independent :: Interaction -> Bool Source #

Can the command run even if the relevant file has not been loaded into the state?

updateInteractionPointsAfter :: Interaction -> Bool Source #

Should Resp_InteractionPoints be issued after the command has run?

interpret :: Interaction -> CommandM () Source #

Interpret an interaction

solveInstantiatedGoals :: Rewrite -> Maybe InteractionId -> CommandM () Source #

Solved goals already instantiated internally The second argument potentially limits it to one specific goal.

cmd_load' Source #

Arguments

:: FilePath 
-> [String] 
-> Bool

Allow unsolved meta-variables?

-> Mode

Full type-checking, or only scope-checking?

-> ((Interface, MaybeWarnings) -> CommandM ()) 
-> CommandM () 

cmd_load' file argv unsolvedOk cmd loads the module in file file, using argv as the command-line options.

If type checking completes without any exceptions having been encountered then the command cmd r is executed, where r is the result of typeCheckMain.

give_gen Source #

Arguments

:: UseForce

Should safety checks be skipped?

-> InteractionId 
-> Range 
-> String 
-> GiveRefine 
-> CommandM () 

A "give"-like action (give, refine, etc).

give_gen force ii rng s give_ref mk_newtxt acts on interaction point ii occupying range rng, placing the new content given by string s, and replacing ii by the newly created interaction points in the state if safety checks pass (unless force is applied).

sortInteractionPoints :: [InteractionId] -> TCM [InteractionId] Source #

Sorts interaction points based on their ranges.

prettyTypeOfMeta :: Rewrite -> InteractionId -> TCM Doc Source #

Pretty-prints the type of the meta-variable.

prettyContext Source #

Arguments

:: Rewrite

Normalise?

-> Bool

Print the elements in reverse order?

-> InteractionId 
-> TCM Doc 

Pretty-prints the context of the given meta-variable.

cmd_helper_function :: Rewrite -> InteractionId -> Range -> String -> TCM Doc Source #

Create type of application of new helper function that would solve the goal.

cmd_goal_type_context_and :: Doc -> Rewrite -> InteractionId -> Range -> String -> StateT CommandState (TCMT IO) () Source #

Displays the current goal, the given document, and the current context.

Should not modify the state.

showModuleContents :: Rewrite -> Range -> String -> CommandM () Source #

Shows all the top-level names in the given module, along with their types.

searchAbout :: Rewrite -> Range -> String -> CommandM () Source #

Shows all the top-level names in scope which mention all the given identifiers in their type.

whyInScope :: String -> CommandM () Source #

Explain why something is in scope.

setCommandLineOpts :: CommandLineOptions -> CommandM () Source #

Sets the command line options and updates the status information.

status :: CommandM Status Source #

Computes some status information.

Does not change the state.

displayStatus :: CommandM () Source #

Displays or updates status information.

Does not change the state.

display_info :: DisplayInfo -> CommandM () Source #

display_info does what display_info' False does, but additionally displays some status information (see status and displayStatus).

parseAndDoAtToplevel Source #

Arguments

:: (Expr -> TCM Doc)

The command to perform.

-> (Doc -> DisplayInfo)

The name to use for the buffer displaying the output.

-> String

The expression to parse.

-> CommandM () 

Parses and scope checks an expression (using the "inside scope" as the scope), performs the given command with the expression as input, and displays the result.

tellToUpdateHighlighting :: Maybe (HighlightingInfo, HighlightingMethod, ModuleToSource) -> IO [Response] Source #

Tell to highlight the code using the given highlighting info (unless it is Nothing).

tellEmacsToJumpToError :: Range -> [Response] Source #

Tells the Emacs mode to go to the first error position (if any).

Orphan instances

Read AbsolutePath Source # 
Instance details

Read InteractionId Source # 
Instance details

Read a => Read (Range' a) Source #

Note that the grammar implemented by this instance does not necessarily match the current representation of ranges.

Instance details

Read a => Read (Interval' a) Source # 
Instance details

Read a => Read (Position' a) Source # 
Instance details