Copyright | (C) 2019 QBayLogic |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Orestis Melkonian <melkon.or@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Gen
Contents
Description
Generic interface for Term types.
Synopsis
- data Syntax
- class Eq (Ctx term) => Diff term where
- type Ann term :: *
- type Options term :: *
- type Ctx term :: *
- readHistory :: FilePath -> IO (History term (Ctx term))
- initialExpr :: History term (Ctx term) -> term
- topEntity :: String
- handleAnn :: Ann term -> Either Syntax (Ctx term)
- userStyles :: [(String, Attr)]
- initOptions :: Options term
- flagFields :: [(Options term -> Bool, Options term -> Bool -> Options term, String)]
- ppr' :: Options term -> term -> Doc (Ann term)
- patch :: term -> [Ctx term] -> term -> term
- type History term ctx = [HStep term ctx]
- data HStep term ctx = HStep {}
- name :: forall term ctx. Lens' (HStep term ctx) String
- ctx :: forall term ctx ctx. Lens (HStep term ctx) (HStep term ctx) [ctx] [ctx]
- bndrS :: forall term ctx. Lens' (HStep term ctx) String
- before :: forall term ctx. Lens' (HStep term ctx) term
- after :: forall term ctx. Lens' (HStep term ctx) term
Documentation
Syntactic annotations used for highlighting. This should be stored in the pretty-printed code output, in addition to term contexts.
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.
Associated Types
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
.
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.
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.
Each step of the rewrite history contains information about a single rewrite.
Constructors
HStep | |
Instances
(Show ctx, Show term) => Show (HStep term ctx) Source # | |
Generic (HStep term ctx) Source # | |
(Binary ctx, Binary term) => Binary (HStep term ctx) Source # | |
type Rep (HStep term ctx) Source # | |
Defined in Gen type Rep (HStep term ctx) = D1 (MetaData "HStep" "Gen" "rewrite-inspector-0.1.0.11-inplace" False) (C1 (MetaCons "HStep" PrefixI True) ((S1 (MetaSel (Just "_ctx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ctx]) :*: S1 (MetaSel (Just "_bndrS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "_name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "_before") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 term) :*: S1 (MetaSel (Just "_after") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 term))))) |