Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- module Data.Functor.Identity
- type Span = (Position, Position)
- type Position = (Line, Col)
- initPosition :: Position
- initCol :: Col
- initLine :: Line
- mkCol :: Int -> Either String Col
- mkLine :: Int -> Either String Line
- advanceCol :: Position -> Position
- advanceLine :: Position -> Position
- data RefactorType
- class Refactorable t where
- isRefactored :: t -> Maybe RefactorType
- getSpan :: t -> Span
- type Reprinting i m = forall node. Typeable node => node -> m (Maybe (RefactorType, i, Span))
- catchAll :: Monad m => a -> m (Maybe b)
- genReprinting :: (Monad m, Refactorable t, Typeable t, StringLike i) => (t -> m i) -> t -> m (Maybe (RefactorType, i, Span))
- reprint :: (Monad m, Data ast, StringLike i) => Reprinting i m -> ast -> i -> m i
- reprintSort :: (Monad m, Data ast, StringLike i) => Reprinting i m -> ast -> i -> m i
Documentation
module Data.Functor.Identity
type Span = (Position, Position) Source #
Two positions give the lower and upper bounds of a source span
initPosition :: Position Source #
The initial position
advanceCol :: Position -> Position Source #
Given a position, advance by one column
advanceLine :: Position -> Position Source #
Given a position, go down a line, going back to the initial column
data RefactorType Source #
Specify a refactoring type
Instances
Show RefactorType Source # | |
Defined in Text.Reprinter showsPrec :: Int -> RefactorType -> ShowS # show :: RefactorType -> String # showList :: [RefactorType] -> ShowS # |
class Refactorable t where Source #
Infrastructure for building the reprinter "plugins"
isRefactored :: t -> Maybe RefactorType Source #
Instances
Refactorable (Expr Bool) Source # | |
Defined in Text.Reprinter.Example |
type Reprinting i m = forall node. Typeable node => node -> m (Maybe (RefactorType, i, Span)) Source #
Type of a reprinting function
i
is the input type (something with a '[Char]'-like interface)
genReprinting :: (Monad m, Refactorable t, Typeable t, StringLike i) => (t -> m i) -> t -> m (Maybe (RefactorType, i, Span)) Source #
Essentially wraps the refactorable interface
reprint :: (Monad m, Data ast, StringLike i) => Reprinting i m -> ast -> i -> m i Source #
The reprint algorithm takes a refactoring (parameteric in
| some monad m) and turns an arbitrary pretty-printable type ast
| into a monadic 'StringLike i' transformer.
reprintSort :: (Monad m, Data ast, StringLike i) => Reprinting i m -> ast -> i -> m i Source #
The reprint algorithm takes a refactoring (parameteric in
| some monad m) and turns an arbitrary pretty-printable type ast
| into a monadic 'StringLike i' transformer.