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 # | |
Lift a => Lift (Many a :: Type) Source # | |
Data a => Data (Many a) Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Many a -> c (Many a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Many a) # toConstr :: Many a -> Constr # dataTypeOf :: Many a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Many a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a)) # gmapT :: (forall b. Data b => b -> b) -> Many a -> Many a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r # gmapQ :: (forall d. Data d => d -> u) -> Many a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Many a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Many a -> m (Many a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Many a -> m (Many a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Many a -> m (Many a) # | |
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
Data MathStyle Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MathStyle -> c MathStyle # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MathStyle # toConstr :: MathStyle -> Constr # dataTypeOf :: MathStyle -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MathStyle) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathStyle) # gmapT :: (forall b. Data b => b -> b) -> MathStyle -> MathStyle # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MathStyle -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MathStyle -> r # gmapQ :: (forall d. Data d => d -> u) -> MathStyle -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MathStyle -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MathStyle -> m MathStyle # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MathStyle -> m MathStyle # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MathStyle -> m MathStyle # | |
Generic MathStyle Source # | |
Show MathStyle Source # | |
Eq MathStyle Source # | |
Ord MathStyle Source # | |
Defined in Djot.AST | |
Lift MathStyle Source # | |
type Rep MathStyle Source # | |
Instances
Data Format Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format -> c Format # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Format # toConstr :: Format -> Constr # dataTypeOf :: Format -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Format) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format) # gmapT :: (forall b. Data b => b -> b) -> Format -> Format # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r # gmapQ :: (forall d. Data d => d -> u) -> Format -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Format -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format -> m Format # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format -> m Format # | |
Generic Format Source # | |
Show Format Source # | |
Eq Format Source # | |
Ord Format Source # | |
Lift Format Source # | |
type Rep Format Source # | |
Defined in Djot.AST type Rep Format = D1 ('MetaData "Format" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" 'True) (C1 ('MetaCons "Format" 'PrefixI 'True) (S1 ('MetaSel ('Just "unFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Instances
Foldable Node Source # | |
Defined in Djot.AST 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 # | |
Monoid Blocks Source # | |
Monoid Inlines Source # | |
Semigroup Blocks Source # | |
Semigroup Inlines Source # | |
Lift a => Lift (Node a :: Type) Source # | |
Data a => Data (Node a) Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node a -> c (Node a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Node a) # toConstr :: Node a -> Constr # dataTypeOf :: Node a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Node a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a)) # gmapT :: (forall b. Data b => b -> b) -> Node a -> Node a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r # gmapQ :: (forall d. Data d => d -> u) -> Node a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Node a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node a -> m (Node a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node a -> m (Node a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node a -> m (Node a) # | |
Generic (Node a) Source # | |
Show a => Show (Node a) Source # | |
Eq a => Eq (Node a) Source # | |
Ord a => Ord (Node a) Source # | |
type Rep (Node a) Source # | |
Defined in Djot.AST type Rep (Node a) = D1 ('MetaData "Node" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" 'False) (C1 ('MetaCons "Node" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Pos) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))) |
Instances
Data Pos Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pos -> c Pos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pos # dataTypeOf :: Pos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos) # gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r # gmapQ :: (forall d. Data d => d -> u) -> Pos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pos -> m Pos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pos -> m Pos # | |
Monoid Pos Source # | |
Semigroup Pos Source # | |
Generic Pos Source # | |
Show Pos Source # | |
Eq Pos Source # | |
Ord Pos Source # | |
Lift Pos Source # | |
type Rep Pos Source # | |
Defined in Djot.AST type Rep Pos = D1 ('MetaData "Pos" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" '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
Data Doc Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Doc -> c Doc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Doc # dataTypeOf :: Doc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Doc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc) # gmapT :: (forall b. Data b => b -> b) -> Doc -> Doc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r # gmapQ :: (forall d. Data d => d -> u) -> Doc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Doc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Doc -> m Doc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc -> m Doc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Doc -> m Doc # | |
Monoid Doc Source # | |
Semigroup Doc Source # | |
Generic Doc Source # | |
Show Doc Source # | |
Eq Doc Source # | |
Ord Doc Source # | |
Lift Doc Source # | |
type Rep Doc Source # | |
Defined in Djot.AST type Rep Doc = D1 ('MetaData "Doc" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" '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
Data NoteMap Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoteMap -> c NoteMap # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoteMap # toConstr :: NoteMap -> Constr # dataTypeOf :: NoteMap -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoteMap) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoteMap) # gmapT :: (forall b. Data b => b -> b) -> NoteMap -> NoteMap # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoteMap -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoteMap -> r # gmapQ :: (forall d. Data d => d -> u) -> NoteMap -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoteMap -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoteMap -> m NoteMap # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoteMap -> m NoteMap # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoteMap -> m NoteMap # | |
Monoid NoteMap Source # | |
Semigroup NoteMap Source # | |
Generic NoteMap Source # | |
Show NoteMap Source # | |
Eq NoteMap Source # | |
Ord NoteMap Source # | |
Lift NoteMap Source # | |
type Rep NoteMap Source # | |
Defined in Djot.AST type Rep NoteMap = D1 ('MetaData "NoteMap" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" '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 # | |
Lift Attr Source # | |
type Rep Attr Source # | |
Defined in Djot.AST type Rep Attr = D1 ('MetaData "Attr" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" 'True) (C1 ('MetaCons "Attr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, ByteString)]))) |
Instances
Data Target Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Target -> c Target # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Target # toConstr :: Target -> Constr # dataTypeOf :: Target -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Target) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Target) # gmapT :: (forall b. Data b => b -> b) -> Target -> Target # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r # gmapQ :: (forall d. Data d => d -> u) -> Target -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Target -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Target -> m Target # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Target -> m Target # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Target -> m Target # | |
Generic Target Source # | |
Show Target Source # | |
Eq Target Source # | |
Ord Target Source # | |
Lift Target Source # | |
type Rep Target Source # | |
Defined in Djot.AST type Rep Target = D1 ('MetaData "Target" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" '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
Instances
Data Align Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Align -> c Align # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Align # dataTypeOf :: Align -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Align) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Align) # gmapT :: (forall b. Data b => b -> b) -> Align -> Align # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r # gmapQ :: (forall d. Data d => d -> u) -> Align -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Align -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Align -> m Align # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Align -> m Align # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Align -> m Align # | |
Generic Align Source # | |
Show Align Source # | |
Eq Align Source # | |
Ord Align Source # | |
Lift Align Source # | |
type Rep Align Source # | |
Defined in Djot.AST type Rep Align = D1 ('MetaData "Align" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" '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
Data Cell Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell -> c Cell # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell # dataTypeOf :: Cell -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell) # gmapT :: (forall b. Data b => b -> b) -> Cell -> Cell # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r # gmapQ :: (forall d. Data d => d -> u) -> Cell -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cell -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cell -> m Cell # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell # | |
Generic Cell Source # | |
Show Cell Source # | |
Eq Cell Source # | |
Ord Cell Source # | |
Lift Cell Source # | |
type Rep Cell Source # | |
Defined in Djot.AST type Rep Cell = D1 ('MetaData "Cell" "Djot.AST" "djot-0.1.2.2-4mACnvSG6uoAgcYjbo6rwE" '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)))) |
Instances
Data CellType Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CellType -> c CellType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CellType # toConstr :: CellType -> Constr # dataTypeOf :: CellType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CellType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellType) # gmapT :: (forall b. Data b => b -> b) -> CellType -> CellType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CellType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CellType -> r # gmapQ :: (forall d. Data d => d -> u) -> CellType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CellType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CellType -> m CellType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CellType -> m CellType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CellType -> m CellType # | |
Generic CellType Source # | |
Show CellType Source # | |
Eq CellType Source # | |
Ord CellType Source # | |
Lift CellType Source # | |
type Rep CellType Source # | |
Instances
Data Caption Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Caption -> c Caption # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Caption # toConstr :: Caption -> Constr # dataTypeOf :: Caption -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Caption) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption) # gmapT :: (forall b. Data b => b -> b) -> Caption -> Caption # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Caption -> r # gmapQ :: (forall d. Data d => d -> u) -> Caption -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Caption -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Caption -> m Caption # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Caption -> m Caption # | |
Generic Caption Source # | |
Show Caption Source # | |
Eq Caption Source # | |
Ord Caption Source # | |
Lift Caption Source # | |
type Rep Caption Source # | |
data ListSpacing Source #
Instances
data OrderedListAttributes Source #
Instances
data OrderedListDelim Source #
Instances
data OrderedListStyle Source #
Instances
Instances
Data QuoteType Source # | |
Defined in Djot.AST gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QuoteType -> c QuoteType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QuoteType # toConstr :: QuoteType -> Constr # dataTypeOf :: QuoteType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QuoteType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType) # gmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QuoteType -> r # gmapQ :: (forall d. Data d => d -> u) -> QuoteType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> QuoteType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType # | |
Generic QuoteType Source # | |
Show QuoteType Source # | |
Eq QuoteType Source # | |
Ord QuoteType Source # | |
Defined in Djot.AST | |
Lift QuoteType Source # | |
type Rep QuoteType Source # | |
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 #