rewrite-inspector-0.1.0.3: Inspection of rewriting steps

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

Gen

Description

Generic interface for Term types.

Documentation

data Syntax Source #

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 #

Minimal complete definition

ppr', patch

Associated Types

type Ann term :: * Source #

type Options term :: * Source #

type Ctx term :: * Source #

Methods

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

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

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

topEntity :: String Source #

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

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

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

initOptions :: Options term Source #

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

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

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

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

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

data HStep term ctx Source #

Constructors

HStep 

Fields

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 #