Agda-2.6.2.1.20220320: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.TypeChecking.Monad.State

Description

Lenses for TCState and more.

Synopsis

Documentation

resetState :: TCM () Source #

Resets the non-persistent part of the type checking state.

resetAllState :: TCM () Source #

Resets all of the type checking state.

Keep only Benchmark and backend information.

localTCState :: TCM a -> TCM a Source #

Restore TCState after performing subcomputation.

In contrast to localState, the Benchmark info from the subcomputation is saved.

localTCStateSaving :: TCM a -> TCM (a, TCState) Source #

Same as localTCState but also returns the state in which we were just before reverting it.

localTCStateSavingWarnings :: TCM a -> TCM a Source #

Same as localTCState but keep all warnings.

speculateTCState :: TCM (a, SpeculateResult) -> TCM a Source #

Allow rolling back the state changes of a TCM computation.

freshTCM :: TCM a -> TCM (Either TCErr a) Source #

A fresh TCM instance.

The computation is run in a fresh state, with the exception that the persistent state is preserved. If the computation changes the state, then these changes are ignored, except for changes to the persistent state. (Changes to the persistent state are also ignored if errors other than type errors or IO exceptions are encountered.)

Lens for persistent states and its fields

Scope

getScope :: ReadTCState m => m ScopeInfo Source #

Get the current scope.

setScope :: ScopeInfo -> TCM () Source #

Set the current scope.

modifyScope_ :: MonadTCState m => (ScopeInfo -> ScopeInfo) -> m () Source #

Modify the current scope without updating the inverse maps.

modifyScope :: MonadTCState m => (ScopeInfo -> ScopeInfo) -> m () Source #

Modify the current scope.

useScope :: ReadTCState m => Lens' a ScopeInfo -> m a Source #

Get a part of the current scope.

locallyScope :: ReadTCState m => Lens' a ScopeInfo -> (a -> a) -> m b -> m b Source #

Run a computation in a modified scope.

withScope :: ReadTCState m => ScopeInfo -> m a -> m (a, ScopeInfo) Source #

Run a computation in a local scope.

withScope_ :: ReadTCState m => ScopeInfo -> m a -> m a Source #

Same as withScope, but discard the scope from the computation.

localScope :: TCM a -> TCM a Source #

Discard any changes to the scope by a computation.

notInScopeError :: QName -> TCM a Source #

Scope error.

printScope :: String -> Int -> String -> TCM () Source #

Debug print the scope.

Signature

Lens for stSignature and stImports

modifyGlobalDefinition :: MonadTCState m => QName -> (Definition -> Definition) -> m () Source #

Update a possibly imported definition. Warning: changes made to imported definitions (during type checking) will not persist outside the current module. This function is currently used to update the compiled representation of a function during compilation.

withSignature :: (ReadTCState m, MonadTCState m) => Signature -> m a -> m a Source #

Run some computation in a different signature, restore original signature.

Modifiers for rewrite rules

Modifiers for parts of the signature

Top level module

setTopLevelModule :: QName -> TCM () Source #

Set the top-level module. This affects the global module id of freshly generated names.

withTopLevelModule :: QName -> TCM a -> TCM a Source #

Use a different top-level module for a computation. Used when generating names for imported modules.

Foreign code

Interaction output callback

Pattern synonyms

getAllPatternSyns :: ReadTCState m => m PatternSynDefns Source #

Get both local and imported pattern synonyms

Benchmark

getBenchmark :: TCM Benchmark Source #

Lens getter for Benchmark from TCMT.

modifyBenchmark :: (Benchmark -> Benchmark) -> TCM () Source #

Lens modify for Benchmark.

Instance definitions

addImportedInstances :: Signature -> TCM () Source #

Look through the signature and reconstruct the instance table.

clearAnonInstanceDefs :: TCM () Source #

Remove all instances whose type is still unresolved.

addUnknownInstance :: QName -> TCM () Source #

Add an instance whose type is still unresolved.

addNamedInstance Source #

Arguments

:: QName

Name of the instance.

-> QName

Name of the class.

-> TCM () 

Add instance to some `class'.