License | BSD-3-Clause |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Simple Markdown AST and related utilities.
Parametrising Document
with the type of
inline code and code blocks allows us to
inspect and validate Swarm code in descriptions.
See drawMarkdown
for
rendering the descriptions as brick widgets.
Synopsis
- newtype Document c = Document {
- paragraphs :: [Paragraph c]
- newtype Paragraph c = Paragraph {}
- data Node c
- data TxtAttr
- fromTextM :: MonadFail m => Text -> m (Document Syntax)
- fromText :: Text -> Document Syntax
- docToText :: PrettyPrec a => Document a -> Text
- docToMark :: PrettyPrec a => Document a -> Text
- data StreamNode' t
- type StreamNode = StreamNode' Text
- class ToStream a where
- toStream :: a -> [StreamNode]
- toText :: ToStream a => a -> Text
- findCode :: Document Syntax -> [Syntax]
- chunksOf :: Int -> [StreamNode] -> [[StreamNode]]
Markdown document
The top-level markdown document.
Document | |
|
Instances
Markdown paragraphs that contain inline leaf nodes.
The idea is that paragraphs do not have line breaks,
and so the inline elements follow each other.
In particular inline code can be followed by text without
space between them (e.g. `logger`s
).
Instances
Inline leaf nodes.
The raw node is from the raw_annotation extension, and can be used for typesentitiesinvalid code.
Instances
Foldable Node Source # | |
Defined in Swarm.Language.Text.Markdown fold :: Monoid m => Node m -> m # foldMap :: Monoid m => (a -> m) -> Node a -> m # foldMap' :: Monoid m => (a -> m) -> Node a -> m # foldr :: (a -> b -> b) -> b -> Node a -> b # foldr' :: (a -> b -> b) -> b -> Node a -> b # foldl :: (b -> a -> b) -> b -> Node a -> b # foldl' :: (b -> a -> b) -> b -> Node a -> b # foldr1 :: (a -> a -> a) -> Node a -> a # foldl1 :: (a -> a -> a) -> Node a -> a # elem :: Eq a => a -> Node a -> Bool # maximum :: Ord a => Node a -> a # | |
Traversable Node Source # | |
Functor Node Source # | |
Show c => Show (Node c) Source # | |
Eq c => Eq (Node c) Source # | |
PrettyPrec a => ToStream (Node a) Source # | |
Defined in Swarm.Language.Text.Markdown toStream :: Node a -> [StreamNode] Source # |
Simple text attributes that make it easier to find key info in descriptions.
fromTextM :: MonadFail m => Text -> m (Document Syntax) Source #
Read Markdown document and parse&validate the code.
If you want only the document with code as Text
,
use the fromTextPure
function.
Token stream
data StreamNode' t Source #
Token stream that can be easily converted to text or brick widgets.
TODO: #574 Code blocks should probably be handled separately.
Instances
Functor StreamNode' Source # | |
Defined in Swarm.Language.Text.Markdown fmap :: (a -> b) -> StreamNode' a -> StreamNode' b # (<$) :: a -> StreamNode' b -> StreamNode' a # | |
Show t => Show (StreamNode' t) Source # | |
Defined in Swarm.Language.Text.Markdown showsPrec :: Int -> StreamNode' t -> ShowS # show :: StreamNode' t -> String # showList :: [StreamNode' t] -> ShowS # | |
Eq t => Eq (StreamNode' t) Source # | |
Defined in Swarm.Language.Text.Markdown (==) :: StreamNode' t -> StreamNode' t -> Bool # (/=) :: StreamNode' t -> StreamNode' t -> Bool # |
type StreamNode = StreamNode' Text Source #
class ToStream a where Source #
Convert elements to one dimensional stream of nodes, that is easy to format and layout.
If you want to split the stream at line length, use
the chunksOf
function afterward.
toStream :: a -> [StreamNode] Source #
Instances
PrettyPrec a => ToStream (Node a) Source # | |
Defined in Swarm.Language.Text.Markdown toStream :: Node a -> [StreamNode] Source # | |
PrettyPrec a => ToStream (Paragraph a) Source # | |
Defined in Swarm.Language.Text.Markdown toStream :: Paragraph a -> [StreamNode] Source # |
toText :: ToStream a => a -> Text Source #
This is the naive and easy way to get text from markdown document.
Utilities
chunksOf :: Int -> [StreamNode] -> [[StreamNode]] Source #
Get chunks of nodes not exceeding length and broken at word boundary.