rewrite-inspector-0.1.0.11: Inspection of rewriting steps

Copyright(C) 2019 QBayLogic
LicenseBSD2 (see the file LICENSE)
MaintainerOrestis Melkonian <melkon.or@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Gen

Contents

Description

Generic interface for Term types.

Synopsis

Documentation

data Syntax Source #

Syntactic annotations used for highlighting. This should be stored in the pretty-printed code output, in addition to term contexts.

Constructors

Type

type information

Keyword

standard keywords of the language

Literal

literal values (e.g. strings, numbers)

Unique

unique identifiers

Qualifier

qualifiers for modules

Custom String

used for user-supplied styling

Instances
Show Syntax Source # 
Instance details

Defined in Gen

class Eq (Ctx term) => Diff term where Source #

This is the typeclass that the user-supplied term type should implement. It requires all operations, which are necessary for our TUI to runn.

Minimal complete definition

ppr', patch

Associated Types

type Ann term :: * Source #

The type of annotations associated to the given term type.

type Options term :: * Source #

The type of options for the associated pretty-printer for term.

type Ctx term :: * Source #

The type of navigation contexts for values of type term.

Methods

readHistory :: FilePath -> IO (History term (Ctx term)) Source #

Read a rewrite history from a binBooary file on disk.

readHistory :: (Binary term, Binary (Ctx term)) => FilePath -> IO (History term (Ctx term)) Source #

Read a rewrite history from a binBooary file on disk.

initialExpr :: History term (Ctx term) -> term Source #

Given a rewrite history, extract the top-level initial expression.

topEntity :: String Source #

If a binder containing this name exists, display first in the list of binders.

handleAnn :: Ann term -> Either Syntax (Ctx term) Source #

Handle annotations of the pretty-printed code, emitting either syntax elements or navigation contexts.

handleAnn :: Ann term ~ Ctx term => Ann term -> Either Syntax (Ctx term) Source #

Handle annotations of the pretty-printed code, emitting either syntax elements or navigation contexts.

userStyles :: [(String, Attr)] Source #

User-supplied styling for the TUI.

initOptions :: Options term Source #

Initial options for the pretty-printer.

initOptions :: Default (Options term) => Options term Source #

Initial options for the pretty-printer.

flagFields :: [(Options term -> Bool, Options term -> Bool -> Options term, String)] Source #

Provide the boolean flags of the pretty-printing options. NB: Lenses are not used here, due to impredicativity...

ppr' :: Options term -> term -> Doc (Ann term) Source #

Pretty-print a given expression, given some options. The resulting document format should contain syntax/context annotations.

patch :: term -> [Ctx term] -> term -> term Source #

Patch a given expression, given a navigation context to a sub-expression and a new sub-expression to replace it.

Rewrite history.

type History term ctx = [HStep term ctx] Source #

The rewrite history consists of multiple single steps of rewriting.

data HStep term ctx Source #

Each step of the rewrite history contains information about a single rewrite.

Constructors

HStep 

Fields

  • _ctx :: [ctx]

    the current context of the sub-expression being rewritten

  • _bndrS :: String

    the name of the current binder

  • _name :: String

    the name of the applied transformation

  • _before :: term

    the sub-expression before rewriting

  • _after :: term

    the sub-expression after rewriting

Instances
(Show ctx, Show term) => Show (HStep term ctx) Source # 
Instance details

Defined in Gen

Methods

showsPrec :: Int -> HStep term ctx -> ShowS #

show :: HStep term ctx -> String #

showList :: [HStep term ctx] -> ShowS #

Generic (HStep term ctx) Source # 
Instance details

Defined in Gen

Associated Types

type Rep (HStep term ctx) :: Type -> Type #

Methods

from :: HStep term ctx -> Rep (HStep term ctx) x #

to :: Rep (HStep term ctx) x -> HStep term ctx #

(Binary ctx, Binary term) => Binary (HStep term ctx) Source # 
Instance details

Defined in Gen

Methods

put :: HStep term ctx -> Put #

get :: Get (HStep term ctx) #

putList :: [HStep term ctx] -> Put #

type Rep (HStep term ctx) Source # 
Instance details

Defined in Gen

name :: forall term ctx. Lens' (HStep term ctx) String Source #

ctx :: forall term ctx ctx. Lens (HStep term ctx) (HStep term ctx) [ctx] [ctx] Source #

bndrS :: forall term ctx. Lens' (HStep term ctx) String Source #

before :: forall term ctx. Lens' (HStep term ctx) term Source #

after :: forall term ctx. Lens' (HStep term ctx) term Source #