idris-1.1.1: Functional Programming Language with Dependent Types

CopyrightLicense : BSD3
MaintainerThe Idris Community.
Safe HaskellNone
LanguageHaskell2010

Idris.ASTUtils

Description

This implements just a few basic lens-like concepts to ease state updates. Similar to fclabels in approach, just without the extra dependency.

We don't include an explicit export list because everything here is meant to be exported.

Short synopsis: --------------- @ f :: Idris () f = do -- these two steps: detaggable <- fgetState (opt_detaggable . ist_optimisation typeName) fputState (opt_detaggable . ist_optimisation typeName) (not detaggable)

  • - are equivalent to: fmodifyState (opt_detaggable . ist_optimisation typeName) not
  • - of course, the long accessor can be put in a variable;
  • - everything is first-class let detag n = opt_detaggable . ist_optimisation n fputState (detag n1) True fputState (detag n2) False
  • - Note that all these operations handle missing items consistently
  • - and transparently, as prescribed by the default values included
  • - in the definitions of the ist_* functions.
  • -
  • - Especially, it's no longer necessary to have initial values of
  • - data structures copied (possibly inconsistently) all over the compiler. @

Synopsis

Documentation

data Field rec fld Source #

Instances

Category * Field Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

ctxt_lookup :: Name -> Field (Ctxt a) (Maybe a) Source #

Exact-name context lookup; uses Nothing for deleted values (read+write!).

Reading a non-existing value yields Nothing, writing Nothing deletes the value (if it existed).

fgetState :: MonadState s m => Field s a -> m a Source #

fmodifyState :: MonadState s m => Field s a -> (a -> a) -> m () Source #

fputState :: MonadState s m => Field s a -> a -> m () Source #

idris_fixities :: Field IState [FixDecl] Source #

Fixity declarations in an IState

ist_callgraph :: Name -> Field IState CGInfo Source #

callgraph record for the given (exact) name

ist_optimisation :: Name -> Field IState OptInfo Source #

the optimisation record for the given (exact) name

known_terms :: Field IState (Ctxt (Def, RigCount, Injectivity, Accessibility, Totality, MetaInformation)) Source #

TT Context

This has a terrible name, but I'm not sure of a better one that isn't confusingly close to tt_ctxt

opt_inaccessible :: Field OptInfo [(Int, Name)] Source #

two fields of the optimisation record

opts_idrisCmdline :: Field IState [Opt] Source #

Commandline flags

repl_definitions :: Field IState [Name] Source #

Names defined at the repl