djot-0.1.0.0: Parser and renderer for djot light markup syntax.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Djot.AST

Synopsis

Documentation

data Inline Source #

Instances

Instances details
Monoid Inlines Source # 
Instance details

Defined in Djot.AST

Semigroup Inlines Source # 
Instance details

Defined in Djot.AST

Generic Inline Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Show Inline Source # 
Instance details

Defined in Djot.AST

Eq Inline Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Inline -> Inline -> Bool #

(/=) :: Inline -> Inline -> Bool #

Ord Inline Source # 
Instance details

Defined in Djot.AST

type Rep Inline Source # 
Instance details

Defined in Djot.AST

type Rep Inline = D1 ('MetaData "Inline" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) ((((C1 ('MetaCons "Str" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Emph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines))) :+: (C1 ('MetaCons "Strong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: (C1 ('MetaCons "Highlight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: C1 ('MetaCons "Insert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines))))) :+: ((C1 ('MetaCons "Delete" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: (C1 ('MetaCons "Superscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: C1 ('MetaCons "Subscript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)))) :+: (C1 ('MetaCons "Verbatim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: (C1 ('MetaCons "Symbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Math" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MathStyle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)))))) :+: (((C1 ('MetaCons "Link" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Target)) :+: C1 ('MetaCons "Image" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Target))) :+: (C1 ('MetaCons "Span" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: (C1 ('MetaCons "FootnoteReference" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "UrlLink" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))) :+: ((C1 ('MetaCons "EmailLink" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: (C1 ('MetaCons "RawInline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "NonBreakingSpace" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Quoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 QuoteType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: (C1 ('MetaCons "SoftBreak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HardBreak" 'PrefixI 'False) (U1 :: Type -> Type))))))

newtype Many a Source #

Constructors

Many 

Fields

Instances

Instances details
Foldable Many Source # 
Instance details

Defined in Djot.AST

Methods

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 #

toList :: Many a -> [a] #

null :: Many a -> Bool #

length :: Many a -> Int #

elem :: Eq a => a -> Many a -> Bool #

maximum :: Ord a => Many a -> a #

minimum :: Ord a => Many a -> a #

sum :: Num a => Many a -> a #

product :: Num a => Many a -> a #

Traversable Many Source # 
Instance details

Defined in Djot.AST

Methods

traverse :: Applicative f => (a -> f b) -> Many a -> f (Many b) #

sequenceA :: Applicative f => Many (f a) -> f (Many a) #

mapM :: Monad m => (a -> m b) -> Many a -> m (Many b) #

sequence :: Monad m => Many (m a) -> m (Many a) #

Functor Many Source # 
Instance details

Defined in Djot.AST

Methods

fmap :: (a -> b) -> Many a -> Many b #

(<$) :: a -> Many b -> Many a #

Monoid Blocks Source # 
Instance details

Defined in Djot.AST

Monoid Inlines Source # 
Instance details

Defined in Djot.AST

Semigroup Blocks Source # 
Instance details

Defined in Djot.AST

Semigroup Inlines Source # 
Instance details

Defined in Djot.AST

Generic (Many a) Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep (Many a) :: Type -> Type #

Methods

from :: Many a -> Rep (Many a) x #

to :: Rep (Many a) x -> Many a #

Show a => Show (Many a) Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Many a -> ShowS #

show :: Many a -> String #

showList :: [Many a] -> ShowS #

Eq a => Eq (Many a) Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Many a -> Many a -> Bool #

(/=) :: Many a -> Many a -> Bool #

Ord a => Ord (Many a) Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Many a -> Many a -> Ordering #

(<) :: Many a -> Many a -> Bool #

(<=) :: Many a -> Many a -> Bool #

(>) :: Many a -> Many a -> Bool #

(>=) :: Many a -> Many a -> Bool #

max :: Many a -> Many a -> Many a #

min :: Many a -> Many a -> Many a #

type Rep (Many a) Source # 
Instance details

Defined in Djot.AST

type Rep (Many a) = D1 ('MetaData "Many" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'True) (C1 ('MetaCons "Many" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMany") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a))))

data MathStyle Source #

Constructors

DisplayMath 
InlineMath 

Instances

Instances details
Generic MathStyle Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep MathStyle :: Type -> Type #

Show MathStyle Source # 
Instance details

Defined in Djot.AST

Eq MathStyle Source # 
Instance details

Defined in Djot.AST

Ord MathStyle Source # 
Instance details

Defined in Djot.AST

type Rep MathStyle Source # 
Instance details

Defined in Djot.AST

type Rep MathStyle = D1 ('MetaData "MathStyle" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "DisplayMath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InlineMath" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Format Source #

Constructors

Format 

Fields

Instances

Instances details
Generic Format Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Format :: Type -> Type #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Show Format Source # 
Instance details

Defined in Djot.AST

Eq Format Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format Source # 
Instance details

Defined in Djot.AST

type Rep Format Source # 
Instance details

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)))

data Node a Source #

Constructors

Node Pos Attr a 

Instances

Instances details
Foldable Node Source # 
Instance details

Defined in Djot.AST

Methods

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 #

toList :: Node a -> [a] #

null :: Node a -> Bool #

length :: Node a -> Int #

elem :: Eq a => a -> Node a -> Bool #

maximum :: Ord a => Node a -> a #

minimum :: Ord a => Node a -> a #

sum :: Num a => Node a -> a #

product :: Num a => Node a -> a #

Traversable Node Source # 
Instance details

Defined in Djot.AST

Methods

traverse :: Applicative f => (a -> f b) -> Node a -> f (Node b) #

sequenceA :: Applicative f => Node (f a) -> f (Node a) #

mapM :: Monad m => (a -> m b) -> Node a -> m (Node b) #

sequence :: Monad m => Node (m a) -> m (Node a) #

Functor Node Source # 
Instance details

Defined in Djot.AST

Methods

fmap :: (a -> b) -> Node a -> Node b #

(<$) :: a -> Node b -> Node a #

Monoid Blocks Source # 
Instance details

Defined in Djot.AST

Monoid Inlines Source # 
Instance details

Defined in Djot.AST

Semigroup Blocks Source # 
Instance details

Defined in Djot.AST

Semigroup Inlines Source # 
Instance details

Defined in Djot.AST

Generic (Node a) Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

Show a => Show (Node a) Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Node a -> ShowS #

show :: Node a -> String #

showList :: [Node a] -> ShowS #

Eq a => Eq (Node a) Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Node a -> Node a -> Bool #

(/=) :: Node a -> Node a -> Bool #

Ord a => Ord (Node a) Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Node a -> Node a -> Ordering #

(<) :: Node a -> Node a -> Bool #

(<=) :: Node a -> Node a -> Bool #

(>) :: Node a -> Node a -> Bool #

(>=) :: Node a -> Node a -> Bool #

max :: Node a -> Node a -> Node a #

min :: Node a -> Node a -> Node a #

type Rep (Node a) Source # 
Instance details

Defined in Djot.AST

data Pos Source #

Constructors

NoPos 
Pos Int Int Int Int 

Instances

Instances details
Monoid Pos Source # 
Instance details

Defined in Djot.AST

Methods

mempty :: Pos #

mappend :: Pos -> Pos -> Pos #

mconcat :: [Pos] -> Pos #

Semigroup Pos Source # 
Instance details

Defined in Djot.AST

Methods

(<>) :: Pos -> Pos -> Pos #

sconcat :: NonEmpty Pos -> Pos #

stimes :: Integral b => b -> Pos -> Pos #

Generic Pos Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

Show Pos Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Eq Pos Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Ord Pos Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Pos -> Pos -> Ordering #

(<) :: Pos -> Pos -> Bool #

(<=) :: Pos -> Pos -> Bool #

(>) :: Pos -> Pos -> Bool #

(>=) :: Pos -> Pos -> Bool #

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

type Rep Pos Source # 
Instance details

Defined in Djot.AST

addAttr :: Attr -> Node a -> Node a Source #

addPos :: Pos -> Node a -> Node a Source #

data Block Source #

Instances

Instances details
Monoid Blocks Source # 
Instance details

Defined in Djot.AST

Semigroup Blocks Source # 
Instance details

Defined in Djot.AST

Generic Block Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

Show Block Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Eq Block Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Block -> Block -> Bool #

(/=) :: Block -> Block -> Bool #

Ord Block Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Block -> Block -> Ordering #

(<) :: Block -> Block -> Bool #

(<=) :: Block -> Block -> Bool #

(>) :: Block -> Block -> Bool #

(>=) :: Block -> Block -> Bool #

max :: Block -> Block -> Block #

min :: Block -> Block -> Block #

type Rep Block Source # 
Instance details

Defined in Djot.AST

type Rep Block = D1 ('MetaData "Block" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (((C1 ('MetaCons "Para" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)) :+: (C1 ('MetaCons "Section" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Blocks)) :+: C1 ('MetaCons "Heading" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Inlines)))) :+: (C1 ('MetaCons "BlockQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Blocks)) :+: (C1 ('MetaCons "CodeBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "Div" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Blocks))))) :+: ((C1 ('MetaCons "OrderedList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OrderedListAttributes) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ListSpacing) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Blocks]))) :+: (C1 ('MetaCons "BulletList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ListSpacing) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Blocks])) :+: C1 ('MetaCons "TaskList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ListSpacing) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(TaskStatus, Blocks)])))) :+: ((C1 ('MetaCons "DefinitionList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ListSpacing) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(Inlines, Blocks)])) :+: C1 ('MetaCons "ThematicBreak" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Caption)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [[Cell]])) :+: C1 ('MetaCons "RawBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))))

data Doc Source #

Instances

Instances details
Monoid Doc Source # 
Instance details

Defined in Djot.AST

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

Semigroup Doc Source # 
Instance details

Defined in Djot.AST

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Generic Doc Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Show Doc Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Eq Doc Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Doc -> Doc -> Bool #

(/=) :: Doc -> Doc -> Bool #

Ord Doc Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Doc -> Doc -> Ordering #

(<) :: Doc -> Doc -> Bool #

(<=) :: Doc -> Doc -> Bool #

(>) :: Doc -> Doc -> Bool #

(>=) :: Doc -> Doc -> Bool #

max :: Doc -> Doc -> Doc #

min :: Doc -> Doc -> Doc #

type Rep Doc Source # 
Instance details

Defined in Djot.AST

newtype NoteMap Source #

A map from labels to contents.

Constructors

NoteMap 

Instances

Instances details
Monoid NoteMap Source # 
Instance details

Defined in Djot.AST

Semigroup NoteMap Source # 
Instance details

Defined in Djot.AST

Generic NoteMap Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep NoteMap :: Type -> Type #

Methods

from :: NoteMap -> Rep NoteMap x #

to :: Rep NoteMap x -> NoteMap #

Show NoteMap Source # 
Instance details

Defined in Djot.AST

Eq NoteMap Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: NoteMap -> NoteMap -> Bool #

(/=) :: NoteMap -> NoteMap -> Bool #

Ord NoteMap Source # 
Instance details

Defined in Djot.AST

type Rep NoteMap Source # 
Instance details

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))))

newtype ReferenceMap Source #

Instances

Instances details
Monoid ReferenceMap Source # 
Instance details

Defined in Djot.AST

Semigroup ReferenceMap Source # 
Instance details

Defined in Djot.AST

Generic ReferenceMap Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep ReferenceMap :: Type -> Type #

Show ReferenceMap Source # 
Instance details

Defined in Djot.AST

Eq ReferenceMap Source # 
Instance details

Defined in Djot.AST

Ord ReferenceMap Source # 
Instance details

Defined in Djot.AST

type Rep ReferenceMap Source # 
Instance details

Defined in Djot.AST

type Rep ReferenceMap = D1 ('MetaData "ReferenceMap" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'True) (C1 ('MetaCons "ReferenceMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "unReferenceMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ByteString (ByteString, Attr)))))

newtype Attr Source #

Constructors

Attr [(ByteString, ByteString)] 

Instances

Instances details
Data Attr Source # 
Instance details

Defined in Djot.AST

Methods

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 #

toConstr :: Attr -> Constr #

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 # 
Instance details

Defined in Djot.AST

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

Semigroup Attr Source # 
Instance details

Defined in Djot.AST

Methods

(<>) :: Attr -> Attr -> Attr #

sconcat :: NonEmpty Attr -> Attr #

stimes :: Integral b => b -> Attr -> Attr #

Generic Attr Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Attr :: Type -> Type #

Methods

from :: Attr -> Rep Attr x #

to :: Rep Attr x -> Attr #

Show Attr Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Eq Attr Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Attr -> Attr -> Bool #

(/=) :: Attr -> Attr -> Bool #

Ord Attr Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Attr -> Attr -> Ordering #

(<) :: Attr -> Attr -> Bool #

(<=) :: Attr -> Attr -> Bool #

(>) :: Attr -> Attr -> Bool #

(>=) :: Attr -> Attr -> Bool #

max :: Attr -> Attr -> Attr #

min :: Attr -> Attr -> Attr #

type Rep Attr Source # 
Instance details

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)])))

data Target Source #

Instances

Instances details
Generic Target Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Target :: Type -> Type #

Methods

from :: Target -> Rep Target x #

to :: Rep Target x -> Target #

Show Target Source # 
Instance details

Defined in Djot.AST

Eq Target Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Target -> Target -> Bool #

(/=) :: Target -> Target -> Bool #

Ord Target Source # 
Instance details

Defined in Djot.AST

type Rep Target Source # 
Instance details

Defined in Djot.AST

data TaskStatus Source #

Constructors

Complete 
Incomplete 

Instances

Instances details
Generic TaskStatus Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep TaskStatus :: Type -> Type #

Show TaskStatus Source # 
Instance details

Defined in Djot.AST

Eq TaskStatus Source # 
Instance details

Defined in Djot.AST

Ord TaskStatus Source # 
Instance details

Defined in Djot.AST

type Rep TaskStatus Source # 
Instance details

Defined in Djot.AST

type Rep TaskStatus = D1 ('MetaData "TaskStatus" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "Complete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Incomplete" 'PrefixI 'False) (U1 :: Type -> Type))

data Align Source #

Instances

Instances details
Generic Align Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Align :: Type -> Type #

Methods

from :: Align -> Rep Align x #

to :: Rep Align x -> Align #

Show Align Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

Eq Align Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Align -> Align -> Bool #

(/=) :: Align -> Align -> Bool #

Ord Align Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Align -> Align -> Ordering #

(<) :: Align -> Align -> Bool #

(<=) :: Align -> Align -> Bool #

(>) :: Align -> Align -> Bool #

(>=) :: Align -> Align -> Bool #

max :: Align -> Align -> Align #

min :: Align -> Align -> Align #

type Rep Align Source # 
Instance details

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)))

data Cell Source #

Constructors

Cell CellType Align Inlines 

Instances

Instances details
Generic Cell Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Cell :: Type -> Type #

Methods

from :: Cell -> Rep Cell x #

to :: Rep Cell x -> Cell #

Show Cell Source # 
Instance details

Defined in Djot.AST

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Eq Cell Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Cell -> Cell -> Bool #

(/=) :: Cell -> Cell -> Bool #

Ord Cell Source # 
Instance details

Defined in Djot.AST

Methods

compare :: Cell -> Cell -> Ordering #

(<) :: Cell -> Cell -> Bool #

(<=) :: Cell -> Cell -> Bool #

(>) :: Cell -> Cell -> Bool #

(>=) :: Cell -> Cell -> Bool #

max :: Cell -> Cell -> Cell #

min :: Cell -> Cell -> Cell #

type Rep Cell Source # 
Instance details

Defined in Djot.AST

data CellType Source #

Constructors

HeadCell 
BodyCell 

Instances

Instances details
Generic CellType Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep CellType :: Type -> Type #

Methods

from :: CellType -> Rep CellType x #

to :: Rep CellType x -> CellType #

Show CellType Source # 
Instance details

Defined in Djot.AST

Eq CellType Source # 
Instance details

Defined in Djot.AST

Ord CellType Source # 
Instance details

Defined in Djot.AST

type Rep CellType Source # 
Instance details

Defined in Djot.AST

type Rep CellType = D1 ('MetaData "CellType" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "HeadCell" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BodyCell" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Caption Source #

Constructors

Caption Blocks 

Instances

Instances details
Generic Caption Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep Caption :: Type -> Type #

Methods

from :: Caption -> Rep Caption x #

to :: Rep Caption x -> Caption #

Show Caption Source # 
Instance details

Defined in Djot.AST

Eq Caption Source # 
Instance details

Defined in Djot.AST

Methods

(==) :: Caption -> Caption -> Bool #

(/=) :: Caption -> Caption -> Bool #

Ord Caption Source # 
Instance details

Defined in Djot.AST

type Rep Caption Source # 
Instance details

Defined in Djot.AST

type Rep Caption = D1 ('MetaData "Caption" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'True) (C1 ('MetaCons "Caption" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Blocks)))

data ListSpacing Source #

Constructors

Tight 
Loose 

Instances

Instances details
Generic ListSpacing Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep ListSpacing :: Type -> Type #

Show ListSpacing Source # 
Instance details

Defined in Djot.AST

Eq ListSpacing Source # 
Instance details

Defined in Djot.AST

Ord ListSpacing Source # 
Instance details

Defined in Djot.AST

type Rep ListSpacing Source # 
Instance details

Defined in Djot.AST

type Rep ListSpacing = D1 ('MetaData "ListSpacing" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "Tight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Loose" 'PrefixI 'False) (U1 :: Type -> Type))

data OrderedListAttributes Source #

Instances

Instances details
Generic OrderedListAttributes Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep OrderedListAttributes :: Type -> Type #

Show OrderedListAttributes Source # 
Instance details

Defined in Djot.AST

Eq OrderedListAttributes Source # 
Instance details

Defined in Djot.AST

Ord OrderedListAttributes Source # 
Instance details

Defined in Djot.AST

type Rep OrderedListAttributes Source # 
Instance details

Defined in Djot.AST

type Rep OrderedListAttributes = D1 ('MetaData "OrderedListAttributes" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "OrderedListAttributes" 'PrefixI 'True) (S1 ('MetaSel ('Just "orderedListStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OrderedListStyle) :*: (S1 ('MetaSel ('Just "orderedListDelim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OrderedListDelim) :*: S1 ('MetaSel ('Just "orderedListStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))))

data OrderedListDelim Source #

Instances

Instances details
Generic OrderedListDelim Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep OrderedListDelim :: Type -> Type #

Show OrderedListDelim Source # 
Instance details

Defined in Djot.AST

Eq OrderedListDelim Source # 
Instance details

Defined in Djot.AST

Ord OrderedListDelim Source # 
Instance details

Defined in Djot.AST

type Rep OrderedListDelim Source # 
Instance details

Defined in Djot.AST

type Rep OrderedListDelim = D1 ('MetaData "OrderedListDelim" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "RightPeriod" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RightParen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftRightParen" 'PrefixI 'False) (U1 :: Type -> Type)))

data OrderedListStyle Source #

Instances

Instances details
Generic OrderedListStyle Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep OrderedListStyle :: Type -> Type #

Show OrderedListStyle Source # 
Instance details

Defined in Djot.AST

Eq OrderedListStyle Source # 
Instance details

Defined in Djot.AST

Ord OrderedListStyle Source # 
Instance details

Defined in Djot.AST

type Rep OrderedListStyle Source # 
Instance details

Defined in Djot.AST

type Rep OrderedListStyle = D1 ('MetaData "OrderedListStyle" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) ((C1 ('MetaCons "Decimal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LetterUpper" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LetterLower" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RomanUpper" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RomanLower" 'PrefixI 'False) (U1 :: Type -> Type))))

data QuoteType Source #

Constructors

SingleQuotes 
DoubleQuotes 

Instances

Instances details
Generic QuoteType Source # 
Instance details

Defined in Djot.AST

Associated Types

type Rep QuoteType :: Type -> Type #

Show QuoteType Source # 
Instance details

Defined in Djot.AST

Eq QuoteType Source # 
Instance details

Defined in Djot.AST

Ord QuoteType Source # 
Instance details

Defined in Djot.AST

type Rep QuoteType Source # 
Instance details

Defined in Djot.AST

type Rep QuoteType = D1 ('MetaData "QuoteType" "Djot.AST" "djot-0.1.0.0-30egGiMDX30BrytkAWnGwZ" 'False) (C1 ('MetaCons "SingleQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoubleQuotes" 'PrefixI 'False) (U1 :: Type -> Type))