Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Inline
- = Str ByteString
- | Emph Inlines
- | Strong Inlines
- | Highlight Inlines
- | Insert Inlines
- | Delete Inlines
- | Superscript Inlines
- | Subscript Inlines
- | Verbatim ByteString
- | Symbol ByteString
- | Math MathStyle ByteString
- | Link Inlines Target
- | Image Inlines Target
- | Span Inlines
- | FootnoteReference ByteString
- | UrlLink ByteString
- | EmailLink ByteString
- | RawInline Format ByteString
- | NonBreakingSpace
- | Quoted QuoteType Inlines
- | SoftBreak
- | HardBreak
- newtype Many a = Many {}
- type Inlines = Many (Node Inline)
- data MathStyle
- newtype Format = Format {}
- data Node a = Node Pos Attr a
- data Pos
- addAttr :: Attr -> Node a -> Node a
- addPos :: Pos -> Node a -> Node a
- data Block
- = Para Inlines
- | Section Blocks
- | Heading Int Inlines
- | BlockQuote Blocks
- | CodeBlock ByteString ByteString
- | Div Blocks
- | OrderedList OrderedListAttributes ListSpacing [Blocks]
- | BulletList ListSpacing [Blocks]
- | TaskList ListSpacing [(TaskStatus, Blocks)]
- | DefinitionList ListSpacing [(Inlines, Blocks)]
- | ThematicBreak
- | Table (Maybe Caption) [[Cell]]
- | RawBlock Format ByteString
- type Blocks = Many (Node Block)
- data Doc = Doc {}
- newtype NoteMap = NoteMap {}
- insertNote :: ByteString -> Blocks -> NoteMap -> NoteMap
- lookupNote :: ByteString -> NoteMap -> Maybe Blocks
- newtype ReferenceMap = ReferenceMap {}
- insertReference :: ByteString -> (ByteString, Attr) -> ReferenceMap -> ReferenceMap
- lookupReference :: ByteString -> ReferenceMap -> Maybe (ByteString, Attr)
- normalizeLabel :: ByteString -> ByteString
- newtype Attr = Attr [(ByteString, ByteString)]
- data Target
- data TaskStatus
- data Align
- data Cell = Cell CellType Align Inlines
- data CellType
- newtype Caption = Caption Blocks
- data ListSpacing
- data OrderedListAttributes = OrderedListAttributes {}
- data OrderedListDelim
- data OrderedListStyle
- data QuoteType
- delete :: Inlines -> Inlines
- displayMath :: ByteString -> Inlines
- insert :: Inlines -> Inlines
- emailLink :: ByteString -> Inlines
- emph :: Inlines -> Inlines
- footnoteReference :: ByteString -> Inlines
- hardBreak :: Inlines
- highlight :: Inlines -> Inlines
- image :: Inlines -> Target -> Inlines
- inlineMath :: ByteString -> Inlines
- link :: Inlines -> Target -> Inlines
- nonBreakingSpace :: Inlines
- rawInline :: Format -> ByteString -> Inlines
- softBreak :: Inlines
- span_ :: Inlines -> Inlines
- str :: ByteString -> Inlines
- strong :: Inlines -> Inlines
- subscript :: Inlines -> Inlines
- superscript :: Inlines -> Inlines
- singleQuoted :: Inlines -> Inlines
- doubleQuoted :: Inlines -> Inlines
- symbol :: ByteString -> Inlines
- verbatim :: ByteString -> Inlines
- urlLink :: ByteString -> Inlines
- para :: Inlines -> Blocks
- section :: Blocks -> Blocks
- heading :: Int -> Inlines -> Blocks
- blockQuote :: Blocks -> Blocks
- codeBlock :: ByteString -> ByteString -> Blocks
- div :: Blocks -> Blocks
- bulletList :: ListSpacing -> [Blocks] -> Blocks
- orderedList :: OrderedListAttributes -> ListSpacing -> [Blocks] -> Blocks
- definitionList :: ListSpacing -> [(Inlines, Blocks)] -> Blocks
- taskList :: ListSpacing -> [(TaskStatus, Blocks)] -> Blocks
- thematicBreak :: Blocks
- table :: Maybe Caption -> [[Cell]] -> Blocks
- rawBlock :: Format -> ByteString -> Blocks
- inlinesToByteString :: Inlines -> ByteString
Documentation
Instances
Instances
Foldable Many Source # | |
Defined in Djot.AST fold :: Monoid m => Many m -> m # foldMap :: Monoid m => (a -> m) -> Many a -> m # foldMap' :: Monoid m => (a -> m) -> Many a -> m # foldr :: (a -> b -> b) -> b -> Many a -> b # foldr' :: (a -> b -> b) -> b -> Many a -> b # foldl :: (b -> a -> b) -> b -> Many a -> b # foldl' :: (b -> a -> b) -> b -> Many a -> b # foldr1 :: (a -> a -> a) -> Many a -> a # foldl1 :: (a -> a -> a) -> Many a -> a # elem :: Eq a => a -> Many a -> Bool # maximum :: Ord a => Many a -> a # | |
Traversable Many Source # | |
Functor Many Source # | |
Monoid Blocks Source # | |
Monoid Inlines Source # | |
Semigroup Blocks Source # | |
Semigroup Inlines Source # | |
Generic (Many a) Source # | |
Show a => Show (Many a) Source # | |
Eq a => Eq (Many a) Source # | |
Ord a => Ord (Many a) Source # | |
type Rep (Many a) Source # | |
Instances
Generic Format Source # | |
Show Format Source # | |
Eq Format Source # | |
Ord Format Source # | |
type Rep Format Source # | |
Defined in Djot.AST type Rep Format = D1 ('MetaData "Format" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'True) (C1 ('MetaCons "Format" 'PrefixI 'True) (S1 ('MetaSel ('Just "unFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Instances
Instances
Monoid Pos Source # | |
Semigroup Pos Source # | |
Generic Pos Source # | |
Show Pos Source # | |
Eq Pos Source # | |
Ord Pos Source # | |
type Rep Pos Source # | |
Defined in Djot.AST type Rep Pos = D1 ('MetaData "Pos" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "NoPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pos" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))) |
Instances
Instances
Monoid Doc Source # | |
Semigroup Doc Source # | |
Generic Doc Source # | |
Show Doc Source # | |
Eq Doc Source # | |
Ord Doc Source # | |
type Rep Doc Source # | |
Defined in Djot.AST type Rep Doc = D1 ('MetaData "Doc" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "Doc" 'PrefixI 'True) ((S1 ('MetaSel ('Just "docBlocks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Blocks) :*: S1 ('MetaSel ('Just "docFootnotes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NoteMap)) :*: (S1 ('MetaSel ('Just "docReferences") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReferenceMap) :*: (S1 ('MetaSel ('Just "docAutoReferences") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ReferenceMap) :*: S1 ('MetaSel ('Just "docAutoIdentifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set ByteString)))))) |
A map from labels to contents.
Instances
Monoid NoteMap Source # | |
Semigroup NoteMap Source # | |
Generic NoteMap Source # | |
Show NoteMap Source # | |
Eq NoteMap Source # | |
Ord NoteMap Source # | |
type Rep NoteMap Source # | |
Defined in Djot.AST type Rep NoteMap = D1 ('MetaData "NoteMap" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'True) (C1 ('MetaCons "NoteMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNoteMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ByteString Blocks)))) |
insertNote :: ByteString -> Blocks -> NoteMap -> NoteMap Source #
lookupNote :: ByteString -> NoteMap -> Maybe Blocks Source #
newtype ReferenceMap Source #
Instances
insertReference :: ByteString -> (ByteString, Attr) -> ReferenceMap -> ReferenceMap Source #
lookupReference :: ByteString -> ReferenceMap -> Maybe (ByteString, Attr) Source #
Attr [(ByteString, ByteString)] |
Instances
Data Attr Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attr -> c Attr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attr # dataTypeOf :: Attr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Attr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr) # gmapT :: (forall b. Data b => b -> b) -> Attr -> Attr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r # gmapQ :: (forall d. Data d => d -> u) -> Attr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Attr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attr -> m Attr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attr -> m Attr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attr -> m Attr # | |
Monoid Attr Source # | |
Semigroup Attr Source # | |
Generic Attr Source # | |
Show Attr Source # | |
Eq Attr Source # | |
Ord Attr Source # | |
type Rep Attr Source # | |
Defined in Djot.AST type Rep Attr = D1 ('MetaData "Attr" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'True) (C1 ('MetaCons "Attr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, ByteString)]))) |
Instances
Generic Target Source # | |
Show Target Source # | |
Eq Target Source # | |
Ord Target Source # | |
type Rep Target Source # | |
Defined in Djot.AST type Rep Target = D1 ('MetaData "Target" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "Direct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Reference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))) |
data TaskStatus Source #
Instances
Generic TaskStatus Source # | |
Defined in Djot.AST type Rep TaskStatus :: Type -> Type # from :: TaskStatus -> Rep TaskStatus x # to :: Rep TaskStatus x -> TaskStatus # | |
Show TaskStatus Source # | |
Defined in Djot.AST showsPrec :: Int -> TaskStatus -> ShowS # show :: TaskStatus -> String # showList :: [TaskStatus] -> ShowS # | |
Eq TaskStatus Source # | |
Defined in Djot.AST (==) :: TaskStatus -> TaskStatus -> Bool # (/=) :: TaskStatus -> TaskStatus -> Bool # | |
Ord TaskStatus Source # | |
Defined in Djot.AST compare :: TaskStatus -> TaskStatus -> Ordering # (<) :: TaskStatus -> TaskStatus -> Bool # (<=) :: TaskStatus -> TaskStatus -> Bool # (>) :: TaskStatus -> TaskStatus -> Bool # (>=) :: TaskStatus -> TaskStatus -> Bool # max :: TaskStatus -> TaskStatus -> TaskStatus # min :: TaskStatus -> TaskStatus -> TaskStatus # | |
type Rep TaskStatus Source # | |
Instances
Generic Align Source # | |
Show Align Source # | |
Eq Align Source # | |
Ord Align Source # | |
type Rep Align Source # | |
Defined in Djot.AST type Rep Align = D1 ('MetaData "Align" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) ((C1 ('MetaCons "AlignLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlignRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AlignCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlignDefault" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Generic Cell Source # | |
Show Cell Source # | |
Eq Cell Source # | |
Ord Cell Source # | |
type Rep Cell Source # | |
Defined in Djot.AST type Rep Cell = D1 ('MetaData "Cell" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "Cell" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CellType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Align) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)))) |
data ListSpacing Source #
Instances
Generic ListSpacing Source # | |
Defined in Djot.AST type Rep ListSpacing :: Type -> Type # from :: ListSpacing -> Rep ListSpacing x # to :: Rep ListSpacing x -> ListSpacing # | |
Show ListSpacing Source # | |
Defined in Djot.AST showsPrec :: Int -> ListSpacing -> ShowS # show :: ListSpacing -> String # showList :: [ListSpacing] -> ShowS # | |
Eq ListSpacing Source # | |
Defined in Djot.AST (==) :: ListSpacing -> ListSpacing -> Bool # (/=) :: ListSpacing -> ListSpacing -> Bool # | |
Ord ListSpacing Source # | |
Defined in Djot.AST compare :: ListSpacing -> ListSpacing -> Ordering # (<) :: ListSpacing -> ListSpacing -> Bool # (<=) :: ListSpacing -> ListSpacing -> Bool # (>) :: ListSpacing -> ListSpacing -> Bool # (>=) :: ListSpacing -> ListSpacing -> Bool # max :: ListSpacing -> ListSpacing -> ListSpacing # min :: ListSpacing -> ListSpacing -> ListSpacing # | |
type Rep ListSpacing Source # | |
data OrderedListAttributes Source #
Instances
data OrderedListDelim Source #
Instances
data OrderedListStyle Source #
Instances
displayMath :: ByteString -> Inlines Source #
emailLink :: ByteString -> Inlines Source #
inlineMath :: ByteString -> Inlines Source #
str :: ByteString -> Inlines Source #
superscript :: Inlines -> Inlines Source #
singleQuoted :: Inlines -> Inlines Source #
doubleQuoted :: Inlines -> Inlines Source #
symbol :: ByteString -> Inlines Source #
verbatim :: ByteString -> Inlines Source #
urlLink :: ByteString -> Inlines Source #
blockQuote :: Blocks -> Blocks Source #
codeBlock :: ByteString -> ByteString -> Blocks Source #
bulletList :: ListSpacing -> [Blocks] -> Blocks Source #
orderedList :: OrderedListAttributes -> ListSpacing -> [Blocks] -> Blocks Source #
definitionList :: ListSpacing -> [(Inlines, Blocks)] -> Blocks Source #
taskList :: ListSpacing -> [(TaskStatus, Blocks)] -> Blocks Source #