Copyright | (C) 2011-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
The type for Lines will very likely change over time, to enable drawing
lit up multi-character versions of control characters for ^Z
, ^[
,
0xff
, etc. This will make for much nicer diagnostics when
working with protocols.
Synopsis
- data Rendering = Rendering !Delta !Int64 !Int64 (Lines -> Lines) (Delta -> Lines -> Lines)
- class HasRendering c where
- nullRendering :: Rendering -> Bool
- emptyRendering :: Rendering
- class Source t where
- rendered :: Source s => Delta -> s -> Rendering
- class Renderable t where
- data Rendered a = a :@ Rendering
- data Caret = Caret !Delta !ByteString
- class HasCaret t where
- data Careted a = a :^ Caret
- drawCaret :: Delta -> Delta -> Lines -> Lines
- addCaret :: Delta -> Rendering -> Rendering
- caretEffects :: [SGR]
- renderingCaret :: Delta -> ByteString -> Rendering
- data Span = Span !Delta !Delta !ByteString
- class HasSpan t where
- data Spanned a = a :~ Span
- spanEffects :: [SGR]
- drawSpan :: Delta -> Delta -> Delta -> Lines -> Lines
- addSpan :: Delta -> Delta -> Rendering -> Rendering
- data Fixit = Fixit {}
- class HasFixit c where
- drawFixit :: Delta -> Delta -> String -> Delta -> Lines -> Lines
- addFixit :: Delta -> Delta -> String -> Rendering -> Rendering
- type Lines = Array (Int, Int64) ([SGR], Char)
- draw :: [SGR] -> Int -> Int64 -> String -> Lines -> Lines
- ifNear :: Delta -> (Lines -> Lines) -> Delta -> Lines -> Lines
- (.#) :: (Delta -> Lines -> Lines) -> Rendering -> Rendering
Documentation
A Rendering
is a canvas of text that output can be written to.
Instances
class HasRendering c where Source #
rendering :: Lens' c Rendering Source #
renderingDelta :: Lens' c Delta Source #
renderingLine :: Lens' c (Lines -> Lines) Source #
renderingLineBytes :: Lens' c Int64 Source #
renderingLineLen :: Lens' c Int64 Source #
renderingOverlays :: Lens' c (Delta -> Lines -> Lines) Source #
Instances
HasRendering Rendering Source # | |
Defined in Text.Trifecta.Rendering rendering :: Lens' Rendering Rendering Source # renderingDelta :: Lens' Rendering Delta Source # renderingLine :: Lens' Rendering (Lines -> Lines) Source # renderingLineBytes :: Lens' Rendering Int64 Source # renderingLineLen :: Lens' Rendering Int64 Source # renderingOverlays :: Lens' Rendering (Delta -> Lines -> Lines) Source # |
nullRendering :: Rendering -> Bool Source #
Is the Rendering
empty?
>>>
nullRendering emptyRendering
True
>>>
nullRendering exampleRendering
False
emptyRendering :: Rendering Source #
The empty Rendering
, which contains nothing at all.
>>>
show (pretty emptyRendering)
""
class Renderable t where Source #
Instances
Instances
Functor Rendered Source # | |
Foldable Rendered Source # | |
Defined in Text.Trifecta.Rendering fold :: Monoid m => Rendered m -> m # foldMap :: Monoid m => (a -> m) -> Rendered a -> m # foldr :: (a -> b -> b) -> b -> Rendered a -> b # foldr' :: (a -> b -> b) -> b -> Rendered a -> b # foldl :: (b -> a -> b) -> b -> Rendered a -> b # foldl' :: (b -> a -> b) -> b -> Rendered a -> b # foldr1 :: (a -> a -> a) -> Rendered a -> a # foldl1 :: (a -> a -> a) -> Rendered a -> a # elem :: Eq a => a -> Rendered a -> Bool # maximum :: Ord a => Rendered a -> a # minimum :: Ord a => Rendered a -> a # | |
Traversable Rendered Source # | |
Comonad Rendered Source # | |
ComonadApply Rendered Source # | |
Show a => Show (Rendered a) Source # | |
HasDelta (Rendered a) Source # | |
HasBytes (Rendered a) Source # | |
Renderable (Rendered a) Source # | |
Carets
A Caret
marks a point in the input with a simple ^
character.
>>>
plain (pretty (addCaret (Columns 35 35) exampleRendering))
int main(int argc, char ** argv) { int; }<EOF> ^
Instances
Eq Caret Source # | |
Data Caret Source # | |
Defined in Text.Trifecta.Rendering gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Caret -> c Caret # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Caret # dataTypeOf :: Caret -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Caret) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caret) # gmapT :: (forall b. Data b => b -> b) -> Caret -> Caret # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Caret -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Caret -> r # gmapQ :: (forall d. Data d => d -> u) -> Caret -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Caret -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Caret -> m Caret # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Caret -> m Caret # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Caret -> m Caret # | |
Ord Caret Source # | |
Show Caret Source # | |
Generic Caret Source # | |
Semigroup Caret Source # | |
Hashable Caret Source # | |
Defined in Text.Trifecta.Rendering | |
HasDelta Caret Source # | |
HasBytes Caret Source # | |
HasCaret Caret Source # | |
Renderable Caret Source # | |
Reducer Caret Rendering Source # | |
type Rep Caret Source # | |
Defined in Text.Trifecta.Rendering type Rep Caret = D1 (MetaData "Caret" "Text.Trifecta.Rendering" "trifecta-2-3LqJ6YGQno0FNVjGdpeVXY" False) (C1 (MetaCons "Caret" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Delta) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 ByteString))) |
Instances
Functor Careted Source # | |
Foldable Careted Source # | |
Defined in Text.Trifecta.Rendering fold :: Monoid m => Careted m -> m # foldMap :: Monoid m => (a -> m) -> Careted a -> m # foldr :: (a -> b -> b) -> b -> Careted a -> b # foldr' :: (a -> b -> b) -> b -> Careted a -> b # foldl :: (b -> a -> b) -> b -> Careted a -> b # foldl' :: (b -> a -> b) -> b -> Careted a -> b # foldr1 :: (a -> a -> a) -> Careted a -> a # foldl1 :: (a -> a -> a) -> Careted a -> a # elem :: Eq a => a -> Careted a -> Bool # maximum :: Ord a => Careted a -> a # minimum :: Ord a => Careted a -> a # | |
Traversable Careted Source # | |
Comonad Careted Source # | |
ComonadApply Careted Source # | |
Eq a => Eq (Careted a) Source # | |
Data a => Data (Careted a) Source # | |
Defined in Text.Trifecta.Rendering gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Careted a -> c (Careted a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Careted a) # toConstr :: Careted a -> Constr # dataTypeOf :: Careted a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Careted a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Careted a)) # gmapT :: (forall b. Data b => b -> b) -> Careted a -> Careted a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Careted a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Careted a -> r # gmapQ :: (forall d. Data d => d -> u) -> Careted a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Careted a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Careted a -> m (Careted a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Careted a -> m (Careted a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Careted a -> m (Careted a) # | |
Ord a => Ord (Careted a) Source # | |
Defined in Text.Trifecta.Rendering | |
Show a => Show (Careted a) Source # | |
Generic (Careted a) Source # | |
Hashable a => Hashable (Careted a) Source # | |
Defined in Text.Trifecta.Rendering | |
HasDelta (Careted a) Source # | |
HasBytes (Careted a) Source # | |
HasCaret (Careted a) Source # | |
Renderable (Careted a) Source # | |
Reducer (Careted a) Rendering Source # | |
type Rep (Careted a) Source # | |
Defined in Text.Trifecta.Rendering type Rep (Careted a) = D1 (MetaData "Careted" "Text.Trifecta.Rendering" "trifecta-2-3LqJ6YGQno0FNVjGdpeVXY" False) (C1 (MetaCons ":^" (InfixI LeftAssociative 9) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Caret))) |
addCaret :: Delta -> Rendering -> Rendering Source #
Render a caret at a certain position in a Rendering
.
caretEffects :: [SGR] Source #
ANSI terminal style for rendering the caret.
renderingCaret :: Delta -> ByteString -> Rendering Source #
Spans
A Span
marks a range of input characters. If Caret
is a point, then
Span
is a line.
>>>
plain (pretty (addSpan (Columns 35 35) (Columns 38 38) exampleRendering))
int main(int argc, char ** argv) { int; }<EOF> ~~~
Span !Delta !Delta !ByteString |
Instances
Eq Span Source # | |
Data Span Source # | |
Defined in Text.Trifecta.Rendering gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Span -> c Span # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Span # dataTypeOf :: Span -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Span) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span) # gmapT :: (forall b. Data b => b -> b) -> Span -> Span # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r # gmapQ :: (forall d. Data d => d -> u) -> Span -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Span -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Span -> m Span # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Span -> m Span # | |
Ord Span Source # | |
Show Span Source # | |
Generic Span Source # | |
Semigroup Span Source # | |
Hashable Span Source # | |
Defined in Text.Trifecta.Rendering | |
HasSpan Span Source # | |
Renderable Span Source # | |
Reducer Span Rendering Source # | |
type Rep Span Source # | |
Defined in Text.Trifecta.Rendering type Rep Span = D1 (MetaData "Span" "Text.Trifecta.Rendering" "trifecta-2-3LqJ6YGQno0FNVjGdpeVXY" False) (C1 (MetaCons "Span" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Delta) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Delta) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 ByteString)))) |
Annotate an arbitrary piece of data with a Span
, typically its
corresponding input location.
Instances
Functor Spanned Source # | |
Foldable Spanned Source # | |
Defined in Text.Trifecta.Rendering fold :: Monoid m => Spanned m -> m # foldMap :: Monoid m => (a -> m) -> Spanned a -> m # foldr :: (a -> b -> b) -> b -> Spanned a -> b # foldr' :: (a -> b -> b) -> b -> Spanned a -> b # foldl :: (b -> a -> b) -> b -> Spanned a -> b # foldl' :: (b -> a -> b) -> b -> Spanned a -> b # foldr1 :: (a -> a -> a) -> Spanned a -> a # foldl1 :: (a -> a -> a) -> Spanned a -> a # elem :: Eq a => a -> Spanned a -> Bool # maximum :: Ord a => Spanned a -> a # minimum :: Ord a => Spanned a -> a # | |
Traversable Spanned Source # | |
Comonad Spanned Source # | |
ComonadApply Spanned Source # | |
Eq a => Eq (Spanned a) Source # | |
Data a => Data (Spanned a) Source # | |
Defined in Text.Trifecta.Rendering gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Spanned a -> c (Spanned a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Spanned a) # toConstr :: Spanned a -> Constr # dataTypeOf :: Spanned a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Spanned a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Spanned a)) # gmapT :: (forall b. Data b => b -> b) -> Spanned a -> Spanned a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Spanned a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Spanned a -> r # gmapQ :: (forall d. Data d => d -> u) -> Spanned a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Spanned a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Spanned a -> m (Spanned a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Spanned a -> m (Spanned a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Spanned a -> m (Spanned a) # | |
Ord a => Ord (Spanned a) Source # | |
Defined in Text.Trifecta.Rendering | |
Show a => Show (Spanned a) Source # | |
Generic (Spanned a) Source # | |
Hashable a => Hashable (Spanned a) Source # | |
Defined in Text.Trifecta.Rendering | |
HasSpan (Spanned a) Source # | |
Renderable (Spanned a) Source # | |
Reducer (Spanned a) Rendering Source # | |
type Rep (Spanned a) Source # | |
Defined in Text.Trifecta.Rendering type Rep (Spanned a) = D1 (MetaData "Spanned" "Text.Trifecta.Rendering" "trifecta-2-3LqJ6YGQno0FNVjGdpeVXY" False) (C1 (MetaCons ":~" (InfixI LeftAssociative 9) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Span))) |
spanEffects :: [SGR] Source #
ANSI terminal style to render spans with.
Fixits
A Fixit
is a Span
with a suggestion.
>>>
plain (pretty (addFixit (Columns 35 35) (Columns 38 38) "Fix this!" exampleRendering))
int main(int argc, char ** argv) { int; }<EOF> ~~~ Fix this!
Fixit | |
|
Instances
Eq Fixit Source # | |
Data Fixit Source # | |
Defined in Text.Trifecta.Rendering gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixit -> c Fixit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixit # dataTypeOf :: Fixit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixit) # gmapT :: (forall b. Data b => b -> b) -> Fixit -> Fixit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixit -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixit -> m Fixit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixit -> m Fixit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixit -> m Fixit # | |
Ord Fixit Source # | |
Show Fixit Source # | |
Generic Fixit Source # | |
Hashable Fixit Source # | |
Defined in Text.Trifecta.Rendering | |
HasSpan Fixit Source # | |
Renderable Fixit Source # | |
HasFixit Fixit Source # | |
Reducer Fixit Rendering Source # | |
type Rep Fixit Source # | |
Defined in Text.Trifecta.Rendering type Rep Fixit = D1 (MetaData "Fixit" "Text.Trifecta.Rendering" "trifecta-2-3LqJ6YGQno0FNVjGdpeVXY" False) (C1 (MetaCons "Fixit" PrefixI True) (S1 (MetaSel (Just "_fixitSpan") SourceUnpack SourceStrict DecidedStrict) (Rec0 Span) :*: S1 (MetaSel (Just "_fixitReplacement") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))) |
class HasFixit c where Source #
fixit :: Lens' c Fixit Source #
Drawing primitives
type Lines = Array (Int, Int64) ([SGR], Char) Source #
A raw canvas to paint ANSI-styled characters on.