{-# LANGUAGE Strict #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Djot.AST
( Inline(..),
  Many(..),
  Inlines,
  MathStyle(..),
  Format(..),
  Node(Node),
  Pos(..),
  addAttr,
  addPos,
  Block(..),
  Blocks,
  Doc(..),
  NoteMap(..),
  insertNote,
  lookupNote,
  ReferenceMap(..),
  insertReference,
  lookupReference,
  normalizeLabel,
  Attr(..),
  Target(..),
  TaskStatus(..),
  Align(..),
  Cell(..),
  CellType(..),
  Caption(..),
  ListSpacing(..),
  OrderedListAttributes(..),
  OrderedListDelim(..),
  OrderedListStyle(..),
  QuoteType(..),
  delete,
  displayMath,
  insert,
  emailLink,
  emph,
  footnoteReference,
  hardBreak,
  highlight,
  image,
  inlineMath,
  link,
  nonBreakingSpace,
  rawInline,
  softBreak,
  span_,
  str,
  strong,
  subscript,
  superscript,
  singleQuoted,
  doubleQuoted,
  symbol,
  verbatim,
  urlLink,
  para,
  section,
  heading,
  blockQuote,
  codeBlock,
  div,
  bulletList,
  orderedList,
  definitionList,
  taskList,
  thematicBreak,
  table,
  rawBlock,
  inlinesToByteString
  )
where

import Prelude hiding (div)
import Data.ByteString (ByteString)
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import qualified Data.Map.Strict as M
import Data.Set (Set)
import Data.Data (Data, Typeable)
import qualified Data.ByteString.Char8 as B8
import GHC.Generics (Generic)

-- import Debug.Trace

newtype Attr = Attr [(ByteString, ByteString)]
  deriving (Int -> Attr -> ShowS
[Attr] -> ShowS
Attr -> String
(Int -> Attr -> ShowS)
-> (Attr -> String) -> ([Attr] -> ShowS) -> Show Attr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Attr -> ShowS
showsPrec :: Int -> Attr -> ShowS
$cshow :: Attr -> String
show :: Attr -> String
$cshowList :: [Attr] -> ShowS
showList :: [Attr] -> ShowS
Show, Attr -> Attr -> Bool
(Attr -> Attr -> Bool) -> (Attr -> Attr -> Bool) -> Eq Attr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Attr -> Attr -> Bool
== :: Attr -> Attr -> Bool
$c/= :: Attr -> Attr -> Bool
/= :: Attr -> Attr -> Bool
Eq, Eq Attr
Eq Attr =>
(Attr -> Attr -> Ordering)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Bool)
-> (Attr -> Attr -> Attr)
-> (Attr -> Attr -> Attr)
-> Ord Attr
Attr -> Attr -> Bool
Attr -> Attr -> Ordering
Attr -> Attr -> Attr
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Attr -> Attr -> Ordering
compare :: Attr -> Attr -> Ordering
$c< :: Attr -> Attr -> Bool
< :: Attr -> Attr -> Bool
$c<= :: Attr -> Attr -> Bool
<= :: Attr -> Attr -> Bool
$c> :: Attr -> Attr -> Bool
> :: Attr -> Attr -> Bool
$c>= :: Attr -> Attr -> Bool
>= :: Attr -> Attr -> Bool
$cmax :: Attr -> Attr -> Attr
max :: Attr -> Attr -> Attr
$cmin :: Attr -> Attr -> Attr
min :: Attr -> Attr -> Attr
Ord, Typeable, Typeable Attr
Typeable Attr =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Attr -> c Attr)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Attr)
-> (Attr -> Constr)
-> (Attr -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Attr))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr))
-> ((forall b. Data b => b -> b) -> Attr -> Attr)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r)
-> (forall u. (forall d. Data d => d -> u) -> Attr -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Attr -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Attr -> m Attr)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Attr -> m Attr)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Attr -> m Attr)
-> Data Attr
Attr -> Constr
Attr -> DataType
(forall b. Data b => b -> b) -> Attr -> Attr
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Attr -> u
forall u. (forall d. Data d => d -> u) -> Attr -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attr -> c Attr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attr -> c Attr
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Attr -> c Attr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Attr
$ctoConstr :: Attr -> Constr
toConstr :: Attr -> Constr
$cdataTypeOf :: Attr -> DataType
dataTypeOf :: Attr -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attr)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Attr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr)
$cgmapT :: (forall b. Data b => b -> b) -> Attr -> Attr
gmapT :: (forall b. Data b => b -> b) -> Attr -> Attr
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Attr -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Attr -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Attr -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Attr -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Attr -> m Attr
Data, (forall x. Attr -> Rep Attr x)
-> (forall x. Rep Attr x -> Attr) -> Generic Attr
forall x. Rep Attr x -> Attr
forall x. Attr -> Rep Attr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Attr -> Rep Attr x
from :: forall x. Attr -> Rep Attr x
$cto :: forall x. Rep Attr x -> Attr
to :: forall x. Rep Attr x -> Attr
Generic)

instance Semigroup Attr where
  Attr [(ByteString, ByteString)]
as <> :: Attr -> Attr -> Attr
<> Attr [(ByteString, ByteString)]
bs =
    [(ByteString, ByteString)] -> Attr
Attr ([(ByteString, ByteString)] -> Attr)
-> [(ByteString, ByteString)] -> Attr
forall a b. (a -> b) -> a -> b
$ ((ByteString, ByteString)
 -> [(ByteString, ByteString)] -> [(ByteString, ByteString)])
-> [(ByteString, ByteString)]
-> [(ByteString, ByteString)]
-> [(ByteString, ByteString)]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (ByteString, ByteString)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
integrate [(ByteString, ByteString)]
bs [(ByteString, ByteString)]
as

instance Monoid Attr where
  mappend :: Attr -> Attr -> Attr
mappend = Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: Attr
mempty = [(ByteString, ByteString)] -> Attr
Attr [(ByteString, ByteString)]
forall a. Monoid a => a
mempty

integrate :: (ByteString, ByteString)
          -> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
integrate :: (ByteString, ByteString)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
integrate (ByteString
k,ByteString
v) [(ByteString, ByteString)]
kvs =
  case ByteString -> [(ByteString, ByteString)] -> Maybe ByteString
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ByteString
k [(ByteString, ByteString)]
kvs of
    Maybe ByteString
Nothing -> (ByteString
k,ByteString
v) (ByteString, ByteString)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. a -> [a] -> [a]
: [(ByteString, ByteString)]
kvs
    Just ByteString
v'
      | ByteString
k ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"class" ->
        (ByteString
k, ByteString
v ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
v') (ByteString, ByteString)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. a -> [a] -> [a]
: ((ByteString, ByteString) -> Bool)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(ByteString
k',ByteString
_) -> ByteString
k' ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
/= ByteString
"class") [(ByteString, ByteString)]
kvs
      | Bool
otherwise -> [(ByteString, ByteString)]
kvs

data Pos = NoPos | Pos Int Int Int Int -- start line, start col, end line, end col
  deriving (Int -> Pos -> ShowS
[Pos] -> ShowS
Pos -> String
(Int -> Pos -> ShowS)
-> (Pos -> String) -> ([Pos] -> ShowS) -> Show Pos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pos -> ShowS
showsPrec :: Int -> Pos -> ShowS
$cshow :: Pos -> String
show :: Pos -> String
$cshowList :: [Pos] -> ShowS
showList :: [Pos] -> ShowS
Show, Pos -> Pos -> Bool
(Pos -> Pos -> Bool) -> (Pos -> Pos -> Bool) -> Eq Pos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pos -> Pos -> Bool
== :: Pos -> Pos -> Bool
$c/= :: Pos -> Pos -> Bool
/= :: Pos -> Pos -> Bool
Eq, Eq Pos
Eq Pos =>
(Pos -> Pos -> Ordering)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Pos)
-> (Pos -> Pos -> Pos)
-> Ord Pos
Pos -> Pos -> Bool
Pos -> Pos -> Ordering
Pos -> Pos -> Pos
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Pos -> Pos -> Ordering
compare :: Pos -> Pos -> Ordering
$c< :: Pos -> Pos -> Bool
< :: Pos -> Pos -> Bool
$c<= :: Pos -> Pos -> Bool
<= :: Pos -> Pos -> Bool
$c> :: Pos -> Pos -> Bool
> :: Pos -> Pos -> Bool
$c>= :: Pos -> Pos -> Bool
>= :: Pos -> Pos -> Bool
$cmax :: Pos -> Pos -> Pos
max :: Pos -> Pos -> Pos
$cmin :: Pos -> Pos -> Pos
min :: Pos -> Pos -> Pos
Ord, Typeable, Typeable Pos
Typeable Pos =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Pos -> c Pos)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Pos)
-> (Pos -> Constr)
-> (Pos -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Pos))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos))
-> ((forall b. Data b => b -> b) -> Pos -> Pos)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r)
-> (forall u. (forall d. Data d => d -> u) -> Pos -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Pos -> m Pos)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Pos -> m Pos)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Pos -> m Pos)
-> Data Pos
Pos -> Constr
Pos -> DataType
(forall b. Data b => b -> b) -> Pos -> Pos
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u
forall u. (forall d. Data d => d -> u) -> Pos -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pos
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pos -> c Pos
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pos)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pos -> c Pos
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pos -> c Pos
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pos
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pos
$ctoConstr :: Pos -> Constr
toConstr :: Pos -> Constr
$cdataTypeOf :: Pos -> DataType
dataTypeOf :: Pos -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pos)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pos)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pos)
$cgmapT :: (forall b. Data b => b -> b) -> Pos -> Pos
gmapT :: (forall b. Data b => b -> b) -> Pos -> Pos
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pos -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Pos -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Pos -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pos -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pos -> m Pos
Data, (forall x. Pos -> Rep Pos x)
-> (forall x. Rep Pos x -> Pos) -> Generic Pos
forall x. Rep Pos x -> Pos
forall x. Pos -> Rep Pos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Pos -> Rep Pos x
from :: forall x. Pos -> Rep Pos x
$cto :: forall x. Rep Pos x -> Pos
to :: forall x. Rep Pos x -> Pos
Generic)

instance Semigroup Pos where
  Pos Int
sl1 Int
sc1 Int
_ Int
_ <> :: Pos -> Pos -> Pos
<> Pos Int
_ Int
_ Int
el2 Int
ec2 =
    Int -> Int -> Int -> Int -> Pos
Pos Int
sl1 Int
sc1 Int
el2 Int
ec2
  Pos
NoPos <> Pos
_ = Pos
NoPos
  Pos
_ <> Pos
NoPos = Pos
NoPos

instance Monoid Pos where
  mappend :: Pos -> Pos -> Pos
mappend = Pos -> Pos -> Pos
forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: Pos
mempty = Pos
NoPos

data Node a = Node Pos Attr a
  deriving (Int -> Node a -> ShowS
[Node a] -> ShowS
Node a -> String
(Int -> Node a -> ShowS)
-> (Node a -> String) -> ([Node a] -> ShowS) -> Show (Node a)
forall a. Show a => Int -> Node a -> ShowS
forall a. Show a => [Node a] -> ShowS
forall a. Show a => Node a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Node a -> ShowS
showsPrec :: Int -> Node a -> ShowS
$cshow :: forall a. Show a => Node a -> String
show :: Node a -> String
$cshowList :: forall a. Show a => [Node a] -> ShowS
showList :: [Node a] -> ShowS
Show, Node a -> Node a -> Bool
(Node a -> Node a -> Bool)
-> (Node a -> Node a -> Bool) -> Eq (Node a)
forall a. Eq a => Node a -> Node a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Node a -> Node a -> Bool
== :: Node a -> Node a -> Bool
$c/= :: forall a. Eq a => Node a -> Node a -> Bool
/= :: Node a -> Node a -> Bool
Eq, Eq (Node a)
Eq (Node a) =>
(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)
-> (Node a -> Node a -> Node a)
-> (Node a -> Node a -> Node a)
-> Ord (Node a)
Node a -> Node a -> Bool
Node a -> Node a -> Ordering
Node a -> Node a -> Node a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Node a)
forall a. Ord a => Node a -> Node a -> Bool
forall a. Ord a => Node a -> Node a -> Ordering
forall a. Ord a => Node a -> Node a -> Node a
$ccompare :: forall a. Ord a => Node a -> Node a -> Ordering
compare :: Node a -> Node a -> Ordering
$c< :: forall a. Ord a => Node a -> Node a -> Bool
< :: Node a -> Node a -> Bool
$c<= :: forall a. Ord a => Node a -> Node a -> Bool
<= :: Node a -> Node a -> Bool
$c> :: forall a. Ord a => Node a -> Node a -> Bool
> :: Node a -> Node a -> Bool
$c>= :: forall a. Ord a => Node a -> Node a -> Bool
>= :: Node a -> Node a -> Bool
$cmax :: forall a. Ord a => Node a -> Node a -> Node a
max :: Node a -> Node a -> Node a
$cmin :: forall a. Ord a => Node a -> Node a -> Node a
min :: Node a -> Node a -> Node a
Ord, (forall a b. (a -> b) -> Node a -> Node b)
-> (forall a b. a -> Node b -> Node a) -> Functor Node
forall a b. a -> Node b -> Node a
forall a b. (a -> b) -> Node a -> Node b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Node a -> Node b
fmap :: forall a b. (a -> b) -> Node a -> Node b
$c<$ :: forall a b. a -> Node b -> Node a
<$ :: forall a b. a -> Node b -> Node a
Functor, Functor Node
Foldable Node
(Functor Node, Foldable Node) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Node a -> f (Node b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Node (f a) -> f (Node a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Node a -> m (Node b))
-> (forall (m :: * -> *) a. Monad m => Node (m a) -> m (Node a))
-> Traversable Node
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Node (m a) -> m (Node a)
forall (f :: * -> *) a. Applicative f => Node (f a) -> f (Node a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Node a -> m (Node b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Node a -> f (Node b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Node a -> f (Node b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Node a -> f (Node b)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Node (f a) -> f (Node a)
sequenceA :: forall (f :: * -> *) a. Applicative f => Node (f a) -> f (Node a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Node a -> m (Node b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Node a -> m (Node b)
$csequence :: forall (m :: * -> *) a. Monad m => Node (m a) -> m (Node a)
sequence :: forall (m :: * -> *) a. Monad m => Node (m a) -> m (Node a)
Traversable, (forall m. Monoid m => Node m -> m)
-> (forall m a. Monoid m => (a -> m) -> Node a -> m)
-> (forall m a. Monoid m => (a -> m) -> Node a -> m)
-> (forall a b. (a -> b -> b) -> b -> Node a -> b)
-> (forall a b. (a -> b -> b) -> b -> Node a -> b)
-> (forall b a. (b -> a -> b) -> b -> Node a -> b)
-> (forall b a. (b -> a -> b) -> b -> Node a -> b)
-> (forall a. (a -> a -> a) -> Node a -> a)
-> (forall a. (a -> a -> a) -> Node a -> a)
-> (forall a. Node a -> [a])
-> (forall a. Node a -> Bool)
-> (forall a. Node a -> Int)
-> (forall a. Eq a => a -> Node a -> Bool)
-> (forall a. Ord a => Node a -> a)
-> (forall a. Ord a => Node a -> a)
-> (forall a. Num a => Node a -> a)
-> (forall a. Num a => Node a -> a)
-> Foldable Node
forall a. Eq a => a -> Node a -> Bool
forall a. Num a => Node a -> a
forall a. Ord a => Node a -> a
forall m. Monoid m => Node m -> m
forall a. Node a -> Bool
forall a. Node a -> Int
forall a. Node a -> [a]
forall a. (a -> a -> a) -> Node a -> a
forall m a. Monoid m => (a -> m) -> Node a -> m
forall b a. (b -> a -> b) -> b -> Node a -> b
forall a b. (a -> b -> b) -> b -> Node a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Node m -> m
fold :: forall m. Monoid m => Node m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Node a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Node a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Node a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Node a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Node a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Node a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Node a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Node a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Node a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Node a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Node a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Node a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Node a -> a
foldr1 :: forall a. (a -> a -> a) -> Node a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Node a -> a
foldl1 :: forall a. (a -> a -> a) -> Node a -> a
$ctoList :: forall a. Node a -> [a]
toList :: forall a. Node a -> [a]
$cnull :: forall a. Node a -> Bool
null :: forall a. Node a -> Bool
$clength :: forall a. Node a -> Int
length :: forall a. Node a -> Int
$celem :: forall a. Eq a => a -> Node a -> Bool
elem :: forall a. Eq a => a -> Node a -> Bool
$cmaximum :: forall a. Ord a => Node a -> a
maximum :: forall a. Ord a => Node a -> a
$cminimum :: forall a. Ord a => Node a -> a
minimum :: forall a. Ord a => Node a -> a
$csum :: forall a. Num a => Node a -> a
sum :: forall a. Num a => Node a -> a
$cproduct :: forall a. Num a => Node a -> a
product :: forall a. Num a => Node a -> a
Foldable, Typeable, Typeable (Node a)
Typeable (Node a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Node a -> c (Node a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Node a))
-> (Node a -> Constr)
-> (Node a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Node a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a)))
-> ((forall b. Data b => b -> b) -> Node a -> Node a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Node a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Node a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Node a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Node a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Node a -> m (Node a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Node a -> m (Node a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Node a -> m (Node a))
-> Data (Node a)
Node a -> Constr
Node a -> DataType
(forall b. Data b => b -> b) -> Node a -> Node a
forall a. Data a => Typeable (Node a)
forall a. Data a => Node a -> Constr
forall a. Data a => Node a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> Node a -> Node a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Node a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Node a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Node a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node a -> c (Node a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Node a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Node a -> u
forall u. (forall d. Data d => d -> u) -> Node a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Node a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node a -> c (Node a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Node a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node a -> c (Node a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Node a -> c (Node a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Node a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Node a)
$ctoConstr :: forall a. Data a => Node a -> Constr
toConstr :: Node a -> Constr
$cdataTypeOf :: forall a. Data a => Node a -> DataType
dataTypeOf :: Node a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Node a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Node a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Node a -> Node a
gmapT :: (forall b. Data b => b -> b) -> Node a -> Node a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node a -> r
$cgmapQr :: forall a r r'.
Data a =>
(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
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Node a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Node a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Node a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Node a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Node a -> m (Node a)
Data, (forall x. Node a -> Rep (Node a) x)
-> (forall x. Rep (Node a) x -> Node a) -> Generic (Node a)
forall x. Rep (Node a) x -> Node a
forall x. Node a -> Rep (Node a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Node a) x -> Node a
forall a x. Node a -> Rep (Node a) x
$cfrom :: forall a x. Node a -> Rep (Node a) x
from :: forall x. Node a -> Rep (Node a) x
$cto :: forall a x. Rep (Node a) x -> Node a
to :: forall x. Rep (Node a) x -> Node a
Generic)

{-# INLINE addAttr #-}
addAttr :: Attr -> Node a -> Node a
addAttr :: forall a. Attr -> Node a -> Node a
addAttr Attr
attr (Node Pos
pos Attr
attr' a
bs) = Pos -> Attr -> a -> Node a
forall a. Pos -> Attr -> a -> Node a
Node Pos
pos (Attr
attr' Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
attr) a
bs

{-# INLINE addPos #-}
addPos :: Pos -> Node a -> Node a
addPos :: forall a. Pos -> Node a -> Node a
addPos Pos
pos (Node Pos
_ Attr
attr a
bs) = Pos -> Attr -> a -> Node a
forall a. Pos -> Attr -> a -> Node a
Node Pos
pos Attr
attr a
bs

newtype Format = Format { Format -> ByteString
unFormat :: ByteString }
  deriving (Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Format -> ShowS
showsPrec :: Int -> Format -> ShowS
$cshow :: Format -> String
show :: Format -> String
$cshowList :: [Format] -> ShowS
showList :: [Format] -> ShowS
Show, Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
/= :: Format -> Format -> Bool
Eq, Eq Format
Eq Format =>
(Format -> Format -> Ordering)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Bool)
-> (Format -> Format -> Format)
-> (Format -> Format -> Format)
-> Ord Format
Format -> Format -> Bool
Format -> Format -> Ordering
Format -> Format -> Format
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Format -> Format -> Ordering
compare :: Format -> Format -> Ordering
$c< :: Format -> Format -> Bool
< :: Format -> Format -> Bool
$c<= :: Format -> Format -> Bool
<= :: Format -> Format -> Bool
$c> :: Format -> Format -> Bool
> :: Format -> Format -> Bool
$c>= :: Format -> Format -> Bool
>= :: Format -> Format -> Bool
$cmax :: Format -> Format -> Format
max :: Format -> Format -> Format
$cmin :: Format -> Format -> Format
min :: Format -> Format -> Format
Ord, Typeable, Typeable Format
Typeable Format =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Format -> c Format)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Format)
-> (Format -> Constr)
-> (Format -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Format))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format))
-> ((forall b. Data b => b -> b) -> Format -> Format)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Format -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Format -> r)
-> (forall u. (forall d. Data d => d -> u) -> Format -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Format -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Format -> m Format)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Format -> m Format)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Format -> m Format)
-> Data Format
Format -> Constr
Format -> DataType
(forall b. Data b => b -> b) -> Format -> Format
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Format -> u
forall u. (forall d. Data d => d -> u) -> Format -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Format -> m Format
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Format -> m Format
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Format
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Format -> c Format
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Format)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Format -> c Format
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Format -> c Format
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Format
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Format
$ctoConstr :: Format -> Constr
toConstr :: Format -> Constr
$cdataTypeOf :: Format -> DataType
dataTypeOf :: Format -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Format)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Format)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Format)
$cgmapT :: (forall b. Data b => b -> b) -> Format -> Format
gmapT :: (forall b. Data b => b -> b) -> Format -> Format
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Format -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Format -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Format -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Format -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Format -> m Format
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Format -> m Format
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Format -> m Format
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Format -> m Format
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Format -> m Format
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Format -> m Format
Data, (forall x. Format -> Rep Format x)
-> (forall x. Rep Format x -> Format) -> Generic Format
forall x. Rep Format x -> Format
forall x. Format -> Rep Format x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Format -> Rep Format x
from :: forall x. Format -> Rep Format x
$cto :: forall x. Rep Format x -> Format
to :: forall x. Rep Format x -> Format
Generic)

data MathStyle = DisplayMath | InlineMath
  deriving (Int -> MathStyle -> ShowS
[MathStyle] -> ShowS
MathStyle -> String
(Int -> MathStyle -> ShowS)
-> (MathStyle -> String)
-> ([MathStyle] -> ShowS)
-> Show MathStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MathStyle -> ShowS
showsPrec :: Int -> MathStyle -> ShowS
$cshow :: MathStyle -> String
show :: MathStyle -> String
$cshowList :: [MathStyle] -> ShowS
showList :: [MathStyle] -> ShowS
Show, Eq MathStyle
Eq MathStyle =>
(MathStyle -> MathStyle -> Ordering)
-> (MathStyle -> MathStyle -> Bool)
-> (MathStyle -> MathStyle -> Bool)
-> (MathStyle -> MathStyle -> Bool)
-> (MathStyle -> MathStyle -> Bool)
-> (MathStyle -> MathStyle -> MathStyle)
-> (MathStyle -> MathStyle -> MathStyle)
-> Ord MathStyle
MathStyle -> MathStyle -> Bool
MathStyle -> MathStyle -> Ordering
MathStyle -> MathStyle -> MathStyle
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MathStyle -> MathStyle -> Ordering
compare :: MathStyle -> MathStyle -> Ordering
$c< :: MathStyle -> MathStyle -> Bool
< :: MathStyle -> MathStyle -> Bool
$c<= :: MathStyle -> MathStyle -> Bool
<= :: MathStyle -> MathStyle -> Bool
$c> :: MathStyle -> MathStyle -> Bool
> :: MathStyle -> MathStyle -> Bool
$c>= :: MathStyle -> MathStyle -> Bool
>= :: MathStyle -> MathStyle -> Bool
$cmax :: MathStyle -> MathStyle -> MathStyle
max :: MathStyle -> MathStyle -> MathStyle
$cmin :: MathStyle -> MathStyle -> MathStyle
min :: MathStyle -> MathStyle -> MathStyle
Ord, MathStyle -> MathStyle -> Bool
(MathStyle -> MathStyle -> Bool)
-> (MathStyle -> MathStyle -> Bool) -> Eq MathStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MathStyle -> MathStyle -> Bool
== :: MathStyle -> MathStyle -> Bool
$c/= :: MathStyle -> MathStyle -> Bool
/= :: MathStyle -> MathStyle -> Bool
Eq, Typeable, Typeable MathStyle
Typeable MathStyle =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> MathStyle -> c MathStyle)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c MathStyle)
-> (MathStyle -> Constr)
-> (MathStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c MathStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathStyle))
-> ((forall b. Data b => b -> b) -> MathStyle -> MathStyle)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> MathStyle -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> MathStyle -> r)
-> (forall u. (forall d. Data d => d -> u) -> MathStyle -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> MathStyle -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> MathStyle -> m MathStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> MathStyle -> m MathStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> MathStyle -> m MathStyle)
-> Data MathStyle
MathStyle -> Constr
MathStyle -> DataType
(forall b. Data b => b -> b) -> MathStyle -> MathStyle
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MathStyle -> u
forall u. (forall d. Data d => d -> u) -> MathStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MathStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathStyle -> c MathStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathStyle)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathStyle -> c MathStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathStyle -> c MathStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathStyle
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathStyle
$ctoConstr :: MathStyle -> Constr
toConstr :: MathStyle -> Constr
$cdataTypeOf :: MathStyle -> DataType
dataTypeOf :: MathStyle -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathStyle)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathStyle)
$cgmapT :: (forall b. Data b => b -> b) -> MathStyle -> MathStyle
gmapT :: (forall b. Data b => b -> b) -> MathStyle -> MathStyle
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathStyle -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathStyle -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MathStyle -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MathStyle -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MathStyle -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MathStyle -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathStyle -> m MathStyle
Data, (forall x. MathStyle -> Rep MathStyle x)
-> (forall x. Rep MathStyle x -> MathStyle) -> Generic MathStyle
forall x. Rep MathStyle x -> MathStyle
forall x. MathStyle -> Rep MathStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MathStyle -> Rep MathStyle x
from :: forall x. MathStyle -> Rep MathStyle x
$cto :: forall x. Rep MathStyle x -> MathStyle
to :: forall x. Rep MathStyle x -> MathStyle
Generic)

data Target =
    Direct ByteString
  | Reference ByteString
  deriving (Int -> Target -> ShowS
[Target] -> ShowS
Target -> String
(Int -> Target -> ShowS)
-> (Target -> String) -> ([Target] -> ShowS) -> Show Target
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Target -> ShowS
showsPrec :: Int -> Target -> ShowS
$cshow :: Target -> String
show :: Target -> String
$cshowList :: [Target] -> ShowS
showList :: [Target] -> ShowS
Show, Eq Target
Eq Target =>
(Target -> Target -> Ordering)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Bool)
-> (Target -> Target -> Target)
-> (Target -> Target -> Target)
-> Ord Target
Target -> Target -> Bool
Target -> Target -> Ordering
Target -> Target -> Target
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Target -> Target -> Ordering
compare :: Target -> Target -> Ordering
$c< :: Target -> Target -> Bool
< :: Target -> Target -> Bool
$c<= :: Target -> Target -> Bool
<= :: Target -> Target -> Bool
$c> :: Target -> Target -> Bool
> :: Target -> Target -> Bool
$c>= :: Target -> Target -> Bool
>= :: Target -> Target -> Bool
$cmax :: Target -> Target -> Target
max :: Target -> Target -> Target
$cmin :: Target -> Target -> Target
min :: Target -> Target -> Target
Ord, Target -> Target -> Bool
(Target -> Target -> Bool)
-> (Target -> Target -> Bool) -> Eq Target
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
/= :: Target -> Target -> Bool
Eq, Typeable, Typeable Target
Typeable Target =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Target -> c Target)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Target)
-> (Target -> Constr)
-> (Target -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Target))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Target))
-> ((forall b. Data b => b -> b) -> Target -> Target)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Target -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Target -> r)
-> (forall u. (forall d. Data d => d -> u) -> Target -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Target -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Target -> m Target)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Target -> m Target)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Target -> m Target)
-> Data Target
Target -> Constr
Target -> DataType
(forall b. Data b => b -> b) -> Target -> Target
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Target -> u
forall u. (forall d. Data d => d -> u) -> Target -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Target -> m Target
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Target -> m Target
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Target
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Target -> c Target
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Target)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Target)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Target -> c Target
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Target -> c Target
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Target
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Target
$ctoConstr :: Target -> Constr
toConstr :: Target -> Constr
$cdataTypeOf :: Target -> DataType
dataTypeOf :: Target -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Target)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Target)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Target)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Target)
$cgmapT :: (forall b. Data b => b -> b) -> Target -> Target
gmapT :: (forall b. Data b => b -> b) -> Target -> Target
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Target -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Target -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Target -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Target -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Target -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Target -> m Target
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Target -> m Target
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Target -> m Target
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Target -> m Target
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Target -> m Target
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Target -> m Target
Data, (forall x. Target -> Rep Target x)
-> (forall x. Rep Target x -> Target) -> Generic Target
forall x. Rep Target x -> Target
forall x. Target -> Rep Target x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Target -> Rep Target x
from :: forall x. Target -> Rep Target x
$cto :: forall x. Rep Target x -> Target
to :: forall x. Rep Target x -> Target
Generic)

data QuoteType = SingleQuotes | DoubleQuotes
  deriving (Int -> QuoteType -> ShowS
[QuoteType] -> ShowS
QuoteType -> String
(Int -> QuoteType -> ShowS)
-> (QuoteType -> String)
-> ([QuoteType] -> ShowS)
-> Show QuoteType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QuoteType -> ShowS
showsPrec :: Int -> QuoteType -> ShowS
$cshow :: QuoteType -> String
show :: QuoteType -> String
$cshowList :: [QuoteType] -> ShowS
showList :: [QuoteType] -> ShowS
Show, Eq QuoteType
Eq QuoteType =>
(QuoteType -> QuoteType -> Ordering)
-> (QuoteType -> QuoteType -> Bool)
-> (QuoteType -> QuoteType -> Bool)
-> (QuoteType -> QuoteType -> Bool)
-> (QuoteType -> QuoteType -> Bool)
-> (QuoteType -> QuoteType -> QuoteType)
-> (QuoteType -> QuoteType -> QuoteType)
-> Ord QuoteType
QuoteType -> QuoteType -> Bool
QuoteType -> QuoteType -> Ordering
QuoteType -> QuoteType -> QuoteType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QuoteType -> QuoteType -> Ordering
compare :: QuoteType -> QuoteType -> Ordering
$c< :: QuoteType -> QuoteType -> Bool
< :: QuoteType -> QuoteType -> Bool
$c<= :: QuoteType -> QuoteType -> Bool
<= :: QuoteType -> QuoteType -> Bool
$c> :: QuoteType -> QuoteType -> Bool
> :: QuoteType -> QuoteType -> Bool
$c>= :: QuoteType -> QuoteType -> Bool
>= :: QuoteType -> QuoteType -> Bool
$cmax :: QuoteType -> QuoteType -> QuoteType
max :: QuoteType -> QuoteType -> QuoteType
$cmin :: QuoteType -> QuoteType -> QuoteType
min :: QuoteType -> QuoteType -> QuoteType
Ord, QuoteType -> QuoteType -> Bool
(QuoteType -> QuoteType -> Bool)
-> (QuoteType -> QuoteType -> Bool) -> Eq QuoteType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuoteType -> QuoteType -> Bool
== :: QuoteType -> QuoteType -> Bool
$c/= :: QuoteType -> QuoteType -> Bool
/= :: QuoteType -> QuoteType -> Bool
Eq, Typeable, Typeable QuoteType
Typeable QuoteType =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> QuoteType -> c QuoteType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c QuoteType)
-> (QuoteType -> Constr)
-> (QuoteType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c QuoteType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType))
-> ((forall b. Data b => b -> b) -> QuoteType -> QuoteType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> QuoteType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> QuoteType -> r)
-> (forall u. (forall d. Data d => d -> u) -> QuoteType -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> QuoteType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> QuoteType -> m QuoteType)
-> Data QuoteType
QuoteType -> Constr
QuoteType -> DataType
(forall b. Data b => b -> b) -> QuoteType -> QuoteType
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> QuoteType -> u
forall u. (forall d. Data d => d -> u) -> QuoteType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteType -> c QuoteType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QuoteType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteType -> c QuoteType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> QuoteType -> c QuoteType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c QuoteType
$ctoConstr :: QuoteType -> Constr
toConstr :: QuoteType -> Constr
$cdataTypeOf :: QuoteType -> DataType
dataTypeOf :: QuoteType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QuoteType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c QuoteType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QuoteType)
$cgmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType
gmapT :: (forall b. Data b => b -> b) -> QuoteType -> QuoteType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> QuoteType -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> QuoteType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> QuoteType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QuoteType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> QuoteType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> QuoteType -> m QuoteType
Data, (forall x. QuoteType -> Rep QuoteType x)
-> (forall x. Rep QuoteType x -> QuoteType) -> Generic QuoteType
forall x. Rep QuoteType x -> QuoteType
forall x. QuoteType -> Rep QuoteType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. QuoteType -> Rep QuoteType x
from :: forall x. QuoteType -> Rep QuoteType x
$cto :: forall x. Rep QuoteType x -> QuoteType
to :: forall x. Rep QuoteType x -> QuoteType
Generic)

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
    deriving (Int -> Inline -> ShowS
[Inline] -> ShowS
Inline -> String
(Int -> Inline -> ShowS)
-> (Inline -> String) -> ([Inline] -> ShowS) -> Show Inline
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Inline -> ShowS
showsPrec :: Int -> Inline -> ShowS
$cshow :: Inline -> String
show :: Inline -> String
$cshowList :: [Inline] -> ShowS
showList :: [Inline] -> ShowS
Show, Eq Inline
Eq Inline =>
(Inline -> Inline -> Ordering)
-> (Inline -> Inline -> Bool)
-> (Inline -> Inline -> Bool)
-> (Inline -> Inline -> Bool)
-> (Inline -> Inline -> Bool)
-> (Inline -> Inline -> Inline)
-> (Inline -> Inline -> Inline)
-> Ord Inline
Inline -> Inline -> Bool
Inline -> Inline -> Ordering
Inline -> Inline -> Inline
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Inline -> Inline -> Ordering
compare :: Inline -> Inline -> Ordering
$c< :: Inline -> Inline -> Bool
< :: Inline -> Inline -> Bool
$c<= :: Inline -> Inline -> Bool
<= :: Inline -> Inline -> Bool
$c> :: Inline -> Inline -> Bool
> :: Inline -> Inline -> Bool
$c>= :: Inline -> Inline -> Bool
>= :: Inline -> Inline -> Bool
$cmax :: Inline -> Inline -> Inline
max :: Inline -> Inline -> Inline
$cmin :: Inline -> Inline -> Inline
min :: Inline -> Inline -> Inline
Ord, Inline -> Inline -> Bool
(Inline -> Inline -> Bool)
-> (Inline -> Inline -> Bool) -> Eq Inline
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Inline -> Inline -> Bool
== :: Inline -> Inline -> Bool
$c/= :: Inline -> Inline -> Bool
/= :: Inline -> Inline -> Bool
Eq, Typeable, Typeable Inline
Typeable Inline =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Inline -> c Inline)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Inline)
-> (Inline -> Constr)
-> (Inline -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Inline))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline))
-> ((forall b. Data b => b -> b) -> Inline -> Inline)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Inline -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Inline -> r)
-> (forall u. (forall d. Data d => d -> u) -> Inline -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Inline -> m Inline)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Inline -> m Inline)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Inline -> m Inline)
-> Data Inline
Inline -> Constr
Inline -> DataType
(forall b. Data b => b -> b) -> Inline -> Inline
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u
forall u. (forall d. Data d => d -> u) -> Inline -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Inline
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inline -> c Inline
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Inline)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inline -> c Inline
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Inline -> c Inline
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Inline
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Inline
$ctoConstr :: Inline -> Constr
toConstr :: Inline -> Constr
$cdataTypeOf :: Inline -> DataType
dataTypeOf :: Inline -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Inline)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Inline)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline)
$cgmapT :: (forall b. Data b => b -> b) -> Inline -> Inline
gmapT :: (forall b. Data b => b -> b) -> Inline -> Inline
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Inline -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Inline -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Inline -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Inline -> m Inline
Data, (forall x. Inline -> Rep Inline x)
-> (forall x. Rep Inline x -> Inline) -> Generic Inline
forall x. Rep Inline x -> Inline
forall x. Inline -> Rep Inline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Inline -> Rep Inline x
from :: forall x. Inline -> Rep Inline x
$cto :: forall x. Rep Inline x -> Inline
to :: forall x. Rep Inline x -> Inline
Generic)

newtype Many a = Many { forall a. Many a -> Seq a
unMany :: Seq a }
  deriving (Int -> Many a -> ShowS
[Many a] -> ShowS
Many a -> String
(Int -> Many a -> ShowS)
-> (Many a -> String) -> ([Many a] -> ShowS) -> Show (Many a)
forall a. Show a => Int -> Many a -> ShowS
forall a. Show a => [Many a] -> ShowS
forall a. Show a => Many a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Many a -> ShowS
showsPrec :: Int -> Many a -> ShowS
$cshow :: forall a. Show a => Many a -> String
show :: Many a -> String
$cshowList :: forall a. Show a => [Many a] -> ShowS
showList :: [Many a] -> ShowS
Show, Eq (Many a)
Eq (Many a) =>
(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)
-> (Many a -> Many a -> Many a)
-> (Many a -> Many a -> Many a)
-> Ord (Many a)
Many a -> Many a -> Bool
Many a -> Many a -> Ordering
Many a -> Many a -> Many a
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (Many a)
forall a. Ord a => Many a -> Many a -> Bool
forall a. Ord a => Many a -> Many a -> Ordering
forall a. Ord a => Many a -> Many a -> Many a
$ccompare :: forall a. Ord a => Many a -> Many a -> Ordering
compare :: Many a -> Many a -> Ordering
$c< :: forall a. Ord a => Many a -> Many a -> Bool
< :: Many a -> Many a -> Bool
$c<= :: forall a. Ord a => Many a -> Many a -> Bool
<= :: Many a -> Many a -> Bool
$c> :: forall a. Ord a => Many a -> Many a -> Bool
> :: Many a -> Many a -> Bool
$c>= :: forall a. Ord a => Many a -> Many a -> Bool
>= :: Many a -> Many a -> Bool
$cmax :: forall a. Ord a => Many a -> Many a -> Many a
max :: Many a -> Many a -> Many a
$cmin :: forall a. Ord a => Many a -> Many a -> Many a
min :: Many a -> Many a -> Many a
Ord, Many a -> Many a -> Bool
(Many a -> Many a -> Bool)
-> (Many a -> Many a -> Bool) -> Eq (Many a)
forall a. Eq a => Many a -> Many a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Many a -> Many a -> Bool
== :: Many a -> Many a -> Bool
$c/= :: forall a. Eq a => Many a -> Many a -> Bool
/= :: Many a -> Many a -> Bool
Eq, (forall a b. (a -> b) -> Many a -> Many b)
-> (forall a b. a -> Many b -> Many a) -> Functor Many
forall a b. a -> Many b -> Many a
forall a b. (a -> b) -> Many a -> Many b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Many a -> Many b
fmap :: forall a b. (a -> b) -> Many a -> Many b
$c<$ :: forall a b. a -> Many b -> Many a
<$ :: forall a b. a -> Many b -> Many a
Functor, Functor Many
Foldable Many
(Functor Many, Foldable Many) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Many a -> f (Many b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Many (f a) -> f (Many a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Many a -> m (Many b))
-> (forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a))
-> Traversable Many
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a)
forall (f :: * -> *) a. Applicative f => Many (f a) -> f (Many a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Many a -> m (Many b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Many a -> f (Many b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Many a -> f (Many b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Many a -> f (Many b)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Many (f a) -> f (Many a)
sequenceA :: forall (f :: * -> *) a. Applicative f => Many (f a) -> f (Many a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Many a -> m (Many b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Many a -> m (Many b)
$csequence :: forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a)
sequence :: forall (m :: * -> *) a. Monad m => Many (m a) -> m (Many a)
Traversable, (forall m. Monoid m => Many m -> m)
-> (forall m a. Monoid m => (a -> m) -> Many a -> m)
-> (forall m a. Monoid m => (a -> m) -> Many a -> m)
-> (forall a b. (a -> b -> b) -> b -> Many a -> b)
-> (forall a b. (a -> b -> b) -> b -> Many a -> b)
-> (forall b a. (b -> a -> b) -> b -> Many a -> b)
-> (forall b a. (b -> a -> b) -> b -> Many a -> b)
-> (forall a. (a -> a -> a) -> Many a -> a)
-> (forall a. (a -> a -> a) -> Many a -> a)
-> (forall a. Many a -> [a])
-> (forall a. Many a -> Bool)
-> (forall a. Many a -> Int)
-> (forall a. Eq a => a -> Many a -> Bool)
-> (forall a. Ord a => Many a -> a)
-> (forall a. Ord a => Many a -> a)
-> (forall a. Num a => Many a -> a)
-> (forall a. Num a => Many a -> a)
-> Foldable Many
forall a. Eq a => a -> Many a -> Bool
forall a. Num a => Many a -> a
forall a. Ord a => Many a -> a
forall m. Monoid m => Many m -> m
forall a. Many a -> Bool
forall a. Many a -> Int
forall a. Many a -> [a]
forall a. (a -> a -> a) -> Many a -> a
forall m a. Monoid m => (a -> m) -> Many a -> m
forall b a. (b -> a -> b) -> b -> Many a -> b
forall a b. (a -> b -> b) -> b -> Many a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Many m -> m
fold :: forall m. Monoid m => Many m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Many a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Many a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Many a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Many a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Many a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Many a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Many a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Many a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Many a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Many a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Many a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Many a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Many a -> a
foldr1 :: forall a. (a -> a -> a) -> Many a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Many a -> a
foldl1 :: forall a. (a -> a -> a) -> Many a -> a
$ctoList :: forall a. Many a -> [a]
toList :: forall a. Many a -> [a]
$cnull :: forall a. Many a -> Bool
null :: forall a. Many a -> Bool
$clength :: forall a. Many a -> Int
length :: forall a. Many a -> Int
$celem :: forall a. Eq a => a -> Many a -> Bool
elem :: forall a. Eq a => a -> Many a -> Bool
$cmaximum :: forall a. Ord a => Many a -> a
maximum :: forall a. Ord a => Many a -> a
$cminimum :: forall a. Ord a => Many a -> a
minimum :: forall a. Ord a => Many a -> a
$csum :: forall a. Num a => Many a -> a
sum :: forall a. Num a => Many a -> a
$cproduct :: forall a. Num a => Many a -> a
product :: forall a. Num a => Many a -> a
Foldable, Typeable, Typeable (Many a)
Typeable (Many a) =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Many a -> c (Many a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Many a))
-> (Many a -> Constr)
-> (Many a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Many a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a)))
-> ((forall b. Data b => b -> b) -> Many a -> Many a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Many a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Many a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Many a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Many a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Many a -> m (Many a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Many a -> m (Many a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Many a -> m (Many a))
-> Data (Many a)
Many a -> Constr
Many a -> DataType
(forall b. Data b => b -> b) -> Many a -> Many a
forall a. Data a => Typeable (Many a)
forall a. Data a => Many a -> Constr
forall a. Data a => Many a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b) -> Many a -> Many a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Many a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> Many a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Many a -> u
forall u. (forall d. Data d => d -> u) -> Many a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Many a -> c (Many a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Many a)
$ctoConstr :: forall a. Data a => Many a -> Constr
toConstr :: Many a -> Constr
$cdataTypeOf :: forall a. Data a => Many a -> DataType
dataTypeOf :: Many a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Many a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Many a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Many a -> Many a
gmapT :: (forall b. Data b => b -> b) -> Many a -> Many a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Many a -> r
$cgmapQr :: forall a r r'.
Data a =>
(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
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> Many a -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Many a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Many a -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Many a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Many a -> m (Many a)
Data, (forall x. Many a -> Rep (Many a) x)
-> (forall x. Rep (Many a) x -> Many a) -> Generic (Many a)
forall x. Rep (Many a) x -> Many a
forall x. Many a -> Rep (Many a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Many a) x -> Many a
forall a x. Many a -> Rep (Many a) x
$cfrom :: forall a x. Many a -> Rep (Many a) x
from :: forall x. Many a -> Rep (Many a) x
$cto :: forall a x. Rep (Many a) x -> Many a
to :: forall x. Rep (Many a) x -> Many a
Generic)

type Inlines = Many (Node Inline)

instance Semigroup Inlines where
  Many Seq (Node Inline)
as <> :: Inlines -> Inlines -> Inlines
<> Many Seq (Node Inline)
bs =
    case (Seq (Node Inline) -> ViewR (Node Inline)
forall a. Seq a -> ViewR a
Seq.viewr Seq (Node Inline)
as, Seq (Node Inline) -> ViewL (Node Inline)
forall a. Seq a -> ViewL a
Seq.viewl Seq (Node Inline)
bs) of
      (Seq (Node Inline)
as' Seq.:> Node Pos
pos1 Attr
attr (Str ByteString
s), Node Pos
pos2 Attr
attr' (Str ByteString
t) Seq.:< Seq (Node Inline)
bs')
        | Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
forall a. Monoid a => a
mempty Bool -> Bool -> Bool
&& Attr
attr' Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
/= Attr
forall a. Monoid a => a
mempty
        , (ByteString
sa, ByteString
sb) <- (Char -> Bool) -> ByteString -> (ByteString, ByteString)
B8.spanEnd (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpaceOrTab) ByteString
s
        , Bool -> Bool
not (ByteString -> Bool
B8.null ByteString
sb)
          -> if ByteString -> Bool
B8.null ByteString
sa
                then
                  Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many (Seq (Node Inline)
as' Seq (Node Inline) -> Seq (Node Inline) -> Seq (Node Inline)
forall a. Semigroup a => a -> a -> a
<> (Pos -> Attr -> Inline -> Node Inline
forall a. Pos -> Attr -> a -> Node a
Node (Pos
pos1 Pos -> Pos -> Pos
forall a. Semigroup a => a -> a -> a
<> Pos
pos2) Attr
attr' (ByteString -> Inline
Str (ByteString
s ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
t)) Node Inline -> Seq (Node Inline) -> Seq (Node Inline)
forall a. a -> Seq a -> Seq a
Seq.<| Seq (Node Inline)
bs'))
                else
                  let sblen :: Int
sblen = ByteString -> Int
B8.length ((Char -> Bool) -> ByteString -> ByteString
B8.filter (\Char
c -> Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
'\128' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\192') ByteString
sb)
                      (Pos
pos1', Pos
pos2') =
                        case Pos
pos1 Pos -> Pos -> Pos
forall a. Semigroup a => a -> a -> a
<> Pos
pos2 of
                            Pos
NoPos -> (Pos
NoPos, Pos
NoPos)
                            Pos Int
sl Int
sc Int
el Int
ec ->
                              (Int -> Int -> Int -> Int -> Pos
Pos Int
sl Int
sc Int
el (Int
ec Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sblen),
                               Int -> Int -> Int -> Int -> Pos
Pos Int
sl (Int
sc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
sblen Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Int
el Int
ec)
                  in  Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many ((Seq (Node Inline)
as' Seq (Node Inline) -> Node Inline -> Seq (Node Inline)
forall a. Seq a -> a -> Seq a
Seq.|> Pos -> Attr -> Inline -> Node Inline
forall a. Pos -> Attr -> a -> Node a
Node Pos
pos1' Attr
forall a. Monoid a => a
mempty (ByteString -> Inline
Str ByteString
sa)
                        Seq (Node Inline) -> Node Inline -> Seq (Node Inline)
forall a. Seq a -> a -> Seq a
Seq.|> Pos -> Attr -> Inline -> Node Inline
forall a. Pos -> Attr -> a -> Node a
Node Pos
pos2' Attr
attr (ByteString -> Inline
Str (ByteString
sb ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
t))) Seq (Node Inline) -> Seq (Node Inline) -> Seq (Node Inline)
forall a. Semigroup a => a -> a -> a
<> Seq (Node Inline)
bs')
        | Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
attr'
          -> Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many (Seq (Node Inline)
as' Seq (Node Inline) -> Seq (Node Inline) -> Seq (Node Inline)
forall a. Semigroup a => a -> a -> a
<> (Pos -> Attr -> Inline -> Node Inline
forall a. Pos -> Attr -> a -> Node a
Node (Pos
pos1 Pos -> Pos -> Pos
forall a. Semigroup a => a -> a -> a
<> Pos
pos2) Attr
attr (ByteString -> Inline
Str (ByteString
s ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
t)) Node Inline -> Seq (Node Inline) -> Seq (Node Inline)
forall a. a -> Seq a -> Seq a
Seq.<| Seq (Node Inline)
bs'))
      (Seq (Node Inline)
as' Seq.:> Node Pos
pos Attr
attr (Str ByteString
s), Node Pos
_ Attr
_ Inline
HardBreak Seq.:< Seq (Node Inline)
_)
        | (Char -> Bool) -> ByteString -> Bool
B8.all Char -> Bool
isSpaceOrTab (Int -> ByteString -> ByteString
B8.takeEnd Int
1 ByteString
s)
          -> Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many (Seq (Node Inline)
as' Seq (Node Inline) -> Seq (Node Inline) -> Seq (Node Inline)
forall a. Semigroup a => a -> a -> a
<> (Pos -> Attr -> Inline -> Node Inline
forall a. Pos -> Attr -> a -> Node a
Node Pos
pos Attr
attr (ByteString -> Inline
Str ((Char -> Bool) -> ByteString -> ByteString
B8.dropWhileEnd Char -> Bool
isSpaceOrTab ByteString
s))
                            Node Inline -> Seq (Node Inline) -> Seq (Node Inline)
forall a. a -> Seq a -> Seq a
Seq.<| Seq (Node Inline)
bs))
      (ViewR (Node Inline), ViewL (Node Inline))
_ -> Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many (Seq (Node Inline)
as Seq (Node Inline) -> Seq (Node Inline) -> Seq (Node Inline)
forall a. Semigroup a => a -> a -> a
<> Seq (Node Inline)
bs)
    where
      isSpaceOrTab :: Char -> Bool
isSpaceOrTab Char
' ' = Bool
True
      isSpaceOrTab Char
'\t' = Bool
True
      isSpaceOrTab Char
_ = Bool
False

instance Monoid Inlines where
  mappend :: Inlines -> Inlines -> Inlines
mappend = Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: Inlines
mempty = Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many Seq (Node Inline)
forall a. Monoid a => a
mempty

data ListSpacing = Tight | Loose
  deriving (Int -> ListSpacing -> ShowS
[ListSpacing] -> ShowS
ListSpacing -> String
(Int -> ListSpacing -> ShowS)
-> (ListSpacing -> String)
-> ([ListSpacing] -> ShowS)
-> Show ListSpacing
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListSpacing -> ShowS
showsPrec :: Int -> ListSpacing -> ShowS
$cshow :: ListSpacing -> String
show :: ListSpacing -> String
$cshowList :: [ListSpacing] -> ShowS
showList :: [ListSpacing] -> ShowS
Show, Eq ListSpacing
Eq ListSpacing =>
(ListSpacing -> ListSpacing -> Ordering)
-> (ListSpacing -> ListSpacing -> Bool)
-> (ListSpacing -> ListSpacing -> Bool)
-> (ListSpacing -> ListSpacing -> Bool)
-> (ListSpacing -> ListSpacing -> Bool)
-> (ListSpacing -> ListSpacing -> ListSpacing)
-> (ListSpacing -> ListSpacing -> ListSpacing)
-> Ord ListSpacing
ListSpacing -> ListSpacing -> Bool
ListSpacing -> ListSpacing -> Ordering
ListSpacing -> ListSpacing -> ListSpacing
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ListSpacing -> ListSpacing -> Ordering
compare :: ListSpacing -> ListSpacing -> Ordering
$c< :: ListSpacing -> ListSpacing -> Bool
< :: ListSpacing -> ListSpacing -> Bool
$c<= :: ListSpacing -> ListSpacing -> Bool
<= :: ListSpacing -> ListSpacing -> Bool
$c> :: ListSpacing -> ListSpacing -> Bool
> :: ListSpacing -> ListSpacing -> Bool
$c>= :: ListSpacing -> ListSpacing -> Bool
>= :: ListSpacing -> ListSpacing -> Bool
$cmax :: ListSpacing -> ListSpacing -> ListSpacing
max :: ListSpacing -> ListSpacing -> ListSpacing
$cmin :: ListSpacing -> ListSpacing -> ListSpacing
min :: ListSpacing -> ListSpacing -> ListSpacing
Ord, ListSpacing -> ListSpacing -> Bool
(ListSpacing -> ListSpacing -> Bool)
-> (ListSpacing -> ListSpacing -> Bool) -> Eq ListSpacing
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListSpacing -> ListSpacing -> Bool
== :: ListSpacing -> ListSpacing -> Bool
$c/= :: ListSpacing -> ListSpacing -> Bool
/= :: ListSpacing -> ListSpacing -> Bool
Eq, Typeable, Typeable ListSpacing
Typeable ListSpacing =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ListSpacing -> c ListSpacing)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ListSpacing)
-> (ListSpacing -> Constr)
-> (ListSpacing -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ListSpacing))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ListSpacing))
-> ((forall b. Data b => b -> b) -> ListSpacing -> ListSpacing)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ListSpacing -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ListSpacing -> r)
-> (forall u. (forall d. Data d => d -> u) -> ListSpacing -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ListSpacing -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing)
-> Data ListSpacing
ListSpacing -> Constr
ListSpacing -> DataType
(forall b. Data b => b -> b) -> ListSpacing -> ListSpacing
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ListSpacing -> u
forall u. (forall d. Data d => d -> u) -> ListSpacing -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListSpacing -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListSpacing -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListSpacing
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListSpacing -> c ListSpacing
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListSpacing)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListSpacing)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListSpacing -> c ListSpacing
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListSpacing -> c ListSpacing
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListSpacing
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListSpacing
$ctoConstr :: ListSpacing -> Constr
toConstr :: ListSpacing -> Constr
$cdataTypeOf :: ListSpacing -> DataType
dataTypeOf :: ListSpacing -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListSpacing)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListSpacing)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListSpacing)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListSpacing)
$cgmapT :: (forall b. Data b => b -> b) -> ListSpacing -> ListSpacing
gmapT :: (forall b. Data b => b -> b) -> ListSpacing -> ListSpacing
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListSpacing -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListSpacing -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListSpacing -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListSpacing -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListSpacing -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ListSpacing -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListSpacing -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListSpacing -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListSpacing -> m ListSpacing
Data, (forall x. ListSpacing -> Rep ListSpacing x)
-> (forall x. Rep ListSpacing x -> ListSpacing)
-> Generic ListSpacing
forall x. Rep ListSpacing x -> ListSpacing
forall x. ListSpacing -> Rep ListSpacing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListSpacing -> Rep ListSpacing x
from :: forall x. ListSpacing -> Rep ListSpacing x
$cto :: forall x. Rep ListSpacing x -> ListSpacing
to :: forall x. Rep ListSpacing x -> ListSpacing
Generic)

data OrderedListStyle =
  Decimal | LetterUpper | LetterLower | RomanUpper | RomanLower
  deriving (Int -> OrderedListStyle -> ShowS
[OrderedListStyle] -> ShowS
OrderedListStyle -> String
(Int -> OrderedListStyle -> ShowS)
-> (OrderedListStyle -> String)
-> ([OrderedListStyle] -> ShowS)
-> Show OrderedListStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OrderedListStyle -> ShowS
showsPrec :: Int -> OrderedListStyle -> ShowS
$cshow :: OrderedListStyle -> String
show :: OrderedListStyle -> String
$cshowList :: [OrderedListStyle] -> ShowS
showList :: [OrderedListStyle] -> ShowS
Show, Eq OrderedListStyle
Eq OrderedListStyle =>
(OrderedListStyle -> OrderedListStyle -> Ordering)
-> (OrderedListStyle -> OrderedListStyle -> Bool)
-> (OrderedListStyle -> OrderedListStyle -> Bool)
-> (OrderedListStyle -> OrderedListStyle -> Bool)
-> (OrderedListStyle -> OrderedListStyle -> Bool)
-> (OrderedListStyle -> OrderedListStyle -> OrderedListStyle)
-> (OrderedListStyle -> OrderedListStyle -> OrderedListStyle)
-> Ord OrderedListStyle
OrderedListStyle -> OrderedListStyle -> Bool
OrderedListStyle -> OrderedListStyle -> Ordering
OrderedListStyle -> OrderedListStyle -> OrderedListStyle
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OrderedListStyle -> OrderedListStyle -> Ordering
compare :: OrderedListStyle -> OrderedListStyle -> Ordering
$c< :: OrderedListStyle -> OrderedListStyle -> Bool
< :: OrderedListStyle -> OrderedListStyle -> Bool
$c<= :: OrderedListStyle -> OrderedListStyle -> Bool
<= :: OrderedListStyle -> OrderedListStyle -> Bool
$c> :: OrderedListStyle -> OrderedListStyle -> Bool
> :: OrderedListStyle -> OrderedListStyle -> Bool
$c>= :: OrderedListStyle -> OrderedListStyle -> Bool
>= :: OrderedListStyle -> OrderedListStyle -> Bool
$cmax :: OrderedListStyle -> OrderedListStyle -> OrderedListStyle
max :: OrderedListStyle -> OrderedListStyle -> OrderedListStyle
$cmin :: OrderedListStyle -> OrderedListStyle -> OrderedListStyle
min :: OrderedListStyle -> OrderedListStyle -> OrderedListStyle
Ord, OrderedListStyle -> OrderedListStyle -> Bool
(OrderedListStyle -> OrderedListStyle -> Bool)
-> (OrderedListStyle -> OrderedListStyle -> Bool)
-> Eq OrderedListStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OrderedListStyle -> OrderedListStyle -> Bool
== :: OrderedListStyle -> OrderedListStyle -> Bool
$c/= :: OrderedListStyle -> OrderedListStyle -> Bool
/= :: OrderedListStyle -> OrderedListStyle -> Bool
Eq, Typeable, Typeable OrderedListStyle
Typeable OrderedListStyle =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> OrderedListStyle -> c OrderedListStyle)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OrderedListStyle)
-> (OrderedListStyle -> Constr)
-> (OrderedListStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OrderedListStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OrderedListStyle))
-> ((forall b. Data b => b -> b)
    -> OrderedListStyle -> OrderedListStyle)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> OrderedListStyle -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OrderedListStyle -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> OrderedListStyle -> m OrderedListStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> OrderedListStyle -> m OrderedListStyle)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> OrderedListStyle -> m OrderedListStyle)
-> Data OrderedListStyle
OrderedListStyle -> Constr
OrderedListStyle -> DataType
(forall b. Data b => b -> b)
-> OrderedListStyle -> OrderedListStyle
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListStyle -> u
forall u. (forall d. Data d => d -> u) -> OrderedListStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedListStyle -> c OrderedListStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListStyle)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedListStyle -> c OrderedListStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedListStyle -> c OrderedListStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListStyle
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListStyle
$ctoConstr :: OrderedListStyle -> Constr
toConstr :: OrderedListStyle -> Constr
$cdataTypeOf :: OrderedListStyle -> DataType
dataTypeOf :: OrderedListStyle -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListStyle)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListStyle)
$cgmapT :: (forall b. Data b => b -> b)
-> OrderedListStyle -> OrderedListStyle
gmapT :: (forall b. Data b => b -> b)
-> OrderedListStyle -> OrderedListStyle
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListStyle -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OrderedListStyle -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OrderedListStyle -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListStyle -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListStyle -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListStyle -> m OrderedListStyle
Data, (forall x. OrderedListStyle -> Rep OrderedListStyle x)
-> (forall x. Rep OrderedListStyle x -> OrderedListStyle)
-> Generic OrderedListStyle
forall x. Rep OrderedListStyle x -> OrderedListStyle
forall x. OrderedListStyle -> Rep OrderedListStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OrderedListStyle -> Rep OrderedListStyle x
from :: forall x. OrderedListStyle -> Rep OrderedListStyle x
$cto :: forall x. Rep OrderedListStyle x -> OrderedListStyle
to :: forall x. Rep OrderedListStyle x -> OrderedListStyle
Generic)

data OrderedListDelim =
  RightPeriod | RightParen | LeftRightParen
  deriving (Int -> OrderedListDelim -> ShowS
[OrderedListDelim] -> ShowS
OrderedListDelim -> String
(Int -> OrderedListDelim -> ShowS)
-> (OrderedListDelim -> String)
-> ([OrderedListDelim] -> ShowS)
-> Show OrderedListDelim
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OrderedListDelim -> ShowS
showsPrec :: Int -> OrderedListDelim -> ShowS
$cshow :: OrderedListDelim -> String
show :: OrderedListDelim -> String
$cshowList :: [OrderedListDelim] -> ShowS
showList :: [OrderedListDelim] -> ShowS
Show, Eq OrderedListDelim
Eq OrderedListDelim =>
(OrderedListDelim -> OrderedListDelim -> Ordering)
-> (OrderedListDelim -> OrderedListDelim -> Bool)
-> (OrderedListDelim -> OrderedListDelim -> Bool)
-> (OrderedListDelim -> OrderedListDelim -> Bool)
-> (OrderedListDelim -> OrderedListDelim -> Bool)
-> (OrderedListDelim -> OrderedListDelim -> OrderedListDelim)
-> (OrderedListDelim -> OrderedListDelim -> OrderedListDelim)
-> Ord OrderedListDelim
OrderedListDelim -> OrderedListDelim -> Bool
OrderedListDelim -> OrderedListDelim -> Ordering
OrderedListDelim -> OrderedListDelim -> OrderedListDelim
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OrderedListDelim -> OrderedListDelim -> Ordering
compare :: OrderedListDelim -> OrderedListDelim -> Ordering
$c< :: OrderedListDelim -> OrderedListDelim -> Bool
< :: OrderedListDelim -> OrderedListDelim -> Bool
$c<= :: OrderedListDelim -> OrderedListDelim -> Bool
<= :: OrderedListDelim -> OrderedListDelim -> Bool
$c> :: OrderedListDelim -> OrderedListDelim -> Bool
> :: OrderedListDelim -> OrderedListDelim -> Bool
$c>= :: OrderedListDelim -> OrderedListDelim -> Bool
>= :: OrderedListDelim -> OrderedListDelim -> Bool
$cmax :: OrderedListDelim -> OrderedListDelim -> OrderedListDelim
max :: OrderedListDelim -> OrderedListDelim -> OrderedListDelim
$cmin :: OrderedListDelim -> OrderedListDelim -> OrderedListDelim
min :: OrderedListDelim -> OrderedListDelim -> OrderedListDelim
Ord, OrderedListDelim -> OrderedListDelim -> Bool
(OrderedListDelim -> OrderedListDelim -> Bool)
-> (OrderedListDelim -> OrderedListDelim -> Bool)
-> Eq OrderedListDelim
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OrderedListDelim -> OrderedListDelim -> Bool
== :: OrderedListDelim -> OrderedListDelim -> Bool
$c/= :: OrderedListDelim -> OrderedListDelim -> Bool
/= :: OrderedListDelim -> OrderedListDelim -> Bool
Eq, Typeable, Typeable OrderedListDelim
Typeable OrderedListDelim =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> OrderedListDelim -> c OrderedListDelim)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OrderedListDelim)
-> (OrderedListDelim -> Constr)
-> (OrderedListDelim -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OrderedListDelim))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OrderedListDelim))
-> ((forall b. Data b => b -> b)
    -> OrderedListDelim -> OrderedListDelim)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> OrderedListDelim -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OrderedListDelim -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> OrderedListDelim -> m OrderedListDelim)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> OrderedListDelim -> m OrderedListDelim)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> OrderedListDelim -> m OrderedListDelim)
-> Data OrderedListDelim
OrderedListDelim -> Constr
OrderedListDelim -> DataType
(forall b. Data b => b -> b)
-> OrderedListDelim -> OrderedListDelim
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListDelim -> u
forall u. (forall d. Data d => d -> u) -> OrderedListDelim -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListDelim
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedListDelim -> c OrderedListDelim
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListDelim)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListDelim)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedListDelim -> c OrderedListDelim
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedListDelim -> c OrderedListDelim
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListDelim
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListDelim
$ctoConstr :: OrderedListDelim -> Constr
toConstr :: OrderedListDelim -> Constr
$cdataTypeOf :: OrderedListDelim -> DataType
dataTypeOf :: OrderedListDelim -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListDelim)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListDelim)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListDelim)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListDelim)
$cgmapT :: (forall b. Data b => b -> b)
-> OrderedListDelim -> OrderedListDelim
gmapT :: (forall b. Data b => b -> b)
-> OrderedListDelim -> OrderedListDelim
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListDelim -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OrderedListDelim -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OrderedListDelim -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListDelim -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListDelim -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListDelim -> m OrderedListDelim
Data, (forall x. OrderedListDelim -> Rep OrderedListDelim x)
-> (forall x. Rep OrderedListDelim x -> OrderedListDelim)
-> Generic OrderedListDelim
forall x. Rep OrderedListDelim x -> OrderedListDelim
forall x. OrderedListDelim -> Rep OrderedListDelim x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OrderedListDelim -> Rep OrderedListDelim x
from :: forall x. OrderedListDelim -> Rep OrderedListDelim x
$cto :: forall x. Rep OrderedListDelim x -> OrderedListDelim
to :: forall x. Rep OrderedListDelim x -> OrderedListDelim
Generic)

data OrderedListAttributes =
  OrderedListAttributes
  { OrderedListAttributes -> OrderedListStyle
orderedListStyle :: OrderedListStyle
  , OrderedListAttributes -> OrderedListDelim
orderedListDelim :: OrderedListDelim
  , OrderedListAttributes -> Int
orderedListStart :: Int }
  deriving (Int -> OrderedListAttributes -> ShowS
[OrderedListAttributes] -> ShowS
OrderedListAttributes -> String
(Int -> OrderedListAttributes -> ShowS)
-> (OrderedListAttributes -> String)
-> ([OrderedListAttributes] -> ShowS)
-> Show OrderedListAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OrderedListAttributes -> ShowS
showsPrec :: Int -> OrderedListAttributes -> ShowS
$cshow :: OrderedListAttributes -> String
show :: OrderedListAttributes -> String
$cshowList :: [OrderedListAttributes] -> ShowS
showList :: [OrderedListAttributes] -> ShowS
Show, Eq OrderedListAttributes
Eq OrderedListAttributes =>
(OrderedListAttributes -> OrderedListAttributes -> Ordering)
-> (OrderedListAttributes -> OrderedListAttributes -> Bool)
-> (OrderedListAttributes -> OrderedListAttributes -> Bool)
-> (OrderedListAttributes -> OrderedListAttributes -> Bool)
-> (OrderedListAttributes -> OrderedListAttributes -> Bool)
-> (OrderedListAttributes
    -> OrderedListAttributes -> OrderedListAttributes)
-> (OrderedListAttributes
    -> OrderedListAttributes -> OrderedListAttributes)
-> Ord OrderedListAttributes
OrderedListAttributes -> OrderedListAttributes -> Bool
OrderedListAttributes -> OrderedListAttributes -> Ordering
OrderedListAttributes
-> OrderedListAttributes -> OrderedListAttributes
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OrderedListAttributes -> OrderedListAttributes -> Ordering
compare :: OrderedListAttributes -> OrderedListAttributes -> Ordering
$c< :: OrderedListAttributes -> OrderedListAttributes -> Bool
< :: OrderedListAttributes -> OrderedListAttributes -> Bool
$c<= :: OrderedListAttributes -> OrderedListAttributes -> Bool
<= :: OrderedListAttributes -> OrderedListAttributes -> Bool
$c> :: OrderedListAttributes -> OrderedListAttributes -> Bool
> :: OrderedListAttributes -> OrderedListAttributes -> Bool
$c>= :: OrderedListAttributes -> OrderedListAttributes -> Bool
>= :: OrderedListAttributes -> OrderedListAttributes -> Bool
$cmax :: OrderedListAttributes
-> OrderedListAttributes -> OrderedListAttributes
max :: OrderedListAttributes
-> OrderedListAttributes -> OrderedListAttributes
$cmin :: OrderedListAttributes
-> OrderedListAttributes -> OrderedListAttributes
min :: OrderedListAttributes
-> OrderedListAttributes -> OrderedListAttributes
Ord, OrderedListAttributes -> OrderedListAttributes -> Bool
(OrderedListAttributes -> OrderedListAttributes -> Bool)
-> (OrderedListAttributes -> OrderedListAttributes -> Bool)
-> Eq OrderedListAttributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OrderedListAttributes -> OrderedListAttributes -> Bool
== :: OrderedListAttributes -> OrderedListAttributes -> Bool
$c/= :: OrderedListAttributes -> OrderedListAttributes -> Bool
/= :: OrderedListAttributes -> OrderedListAttributes -> Bool
Eq, Typeable, Typeable OrderedListAttributes
Typeable OrderedListAttributes =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g)
 -> OrderedListAttributes
 -> c OrderedListAttributes)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c OrderedListAttributes)
-> (OrderedListAttributes -> Constr)
-> (OrderedListAttributes -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c OrderedListAttributes))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c OrderedListAttributes))
-> ((forall b. Data b => b -> b)
    -> OrderedListAttributes -> OrderedListAttributes)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> OrderedListAttributes
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> OrderedListAttributes
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> OrderedListAttributes -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> OrderedListAttributes -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> OrderedListAttributes -> m OrderedListAttributes)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> OrderedListAttributes -> m OrderedListAttributes)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> OrderedListAttributes -> m OrderedListAttributes)
-> Data OrderedListAttributes
OrderedListAttributes -> Constr
OrderedListAttributes -> DataType
(forall b. Data b => b -> b)
-> OrderedListAttributes -> OrderedListAttributes
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListAttributes -> u
forall u.
(forall d. Data d => d -> u) -> OrderedListAttributes -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListAttributes -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListAttributes -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListAttributes
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OrderedListAttributes
-> c OrderedListAttributes
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListAttributes)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListAttributes)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OrderedListAttributes
-> c OrderedListAttributes
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> OrderedListAttributes
-> c OrderedListAttributes
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListAttributes
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedListAttributes
$ctoConstr :: OrderedListAttributes -> Constr
toConstr :: OrderedListAttributes -> Constr
$cdataTypeOf :: OrderedListAttributes -> DataType
dataTypeOf :: OrderedListAttributes -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListAttributes)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedListAttributes)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListAttributes)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedListAttributes)
$cgmapT :: (forall b. Data b => b -> b)
-> OrderedListAttributes -> OrderedListAttributes
gmapT :: (forall b. Data b => b -> b)
-> OrderedListAttributes -> OrderedListAttributes
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListAttributes -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListAttributes -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListAttributes -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedListAttributes -> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> OrderedListAttributes -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> OrderedListAttributes -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListAttributes -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> OrderedListAttributes -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> OrderedListAttributes -> m OrderedListAttributes
Data, (forall x. OrderedListAttributes -> Rep OrderedListAttributes x)
-> (forall x. Rep OrderedListAttributes x -> OrderedListAttributes)
-> Generic OrderedListAttributes
forall x. Rep OrderedListAttributes x -> OrderedListAttributes
forall x. OrderedListAttributes -> Rep OrderedListAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OrderedListAttributes -> Rep OrderedListAttributes x
from :: forall x. OrderedListAttributes -> Rep OrderedListAttributes x
$cto :: forall x. Rep OrderedListAttributes x -> OrderedListAttributes
to :: forall x. Rep OrderedListAttributes x -> OrderedListAttributes
Generic)

data TaskStatus = Complete | Incomplete
  deriving (Int -> TaskStatus -> ShowS
[TaskStatus] -> ShowS
TaskStatus -> String
(Int -> TaskStatus -> ShowS)
-> (TaskStatus -> String)
-> ([TaskStatus] -> ShowS)
-> Show TaskStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TaskStatus -> ShowS
showsPrec :: Int -> TaskStatus -> ShowS
$cshow :: TaskStatus -> String
show :: TaskStatus -> String
$cshowList :: [TaskStatus] -> ShowS
showList :: [TaskStatus] -> ShowS
Show, Eq TaskStatus
Eq TaskStatus =>
(TaskStatus -> TaskStatus -> Ordering)
-> (TaskStatus -> TaskStatus -> Bool)
-> (TaskStatus -> TaskStatus -> Bool)
-> (TaskStatus -> TaskStatus -> Bool)
-> (TaskStatus -> TaskStatus -> Bool)
-> (TaskStatus -> TaskStatus -> TaskStatus)
-> (TaskStatus -> TaskStatus -> TaskStatus)
-> Ord TaskStatus
TaskStatus -> TaskStatus -> Bool
TaskStatus -> TaskStatus -> Ordering
TaskStatus -> TaskStatus -> TaskStatus
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TaskStatus -> TaskStatus -> Ordering
compare :: TaskStatus -> TaskStatus -> Ordering
$c< :: TaskStatus -> TaskStatus -> Bool
< :: TaskStatus -> TaskStatus -> Bool
$c<= :: TaskStatus -> TaskStatus -> Bool
<= :: TaskStatus -> TaskStatus -> Bool
$c> :: TaskStatus -> TaskStatus -> Bool
> :: TaskStatus -> TaskStatus -> Bool
$c>= :: TaskStatus -> TaskStatus -> Bool
>= :: TaskStatus -> TaskStatus -> Bool
$cmax :: TaskStatus -> TaskStatus -> TaskStatus
max :: TaskStatus -> TaskStatus -> TaskStatus
$cmin :: TaskStatus -> TaskStatus -> TaskStatus
min :: TaskStatus -> TaskStatus -> TaskStatus
Ord, TaskStatus -> TaskStatus -> Bool
(TaskStatus -> TaskStatus -> Bool)
-> (TaskStatus -> TaskStatus -> Bool) -> Eq TaskStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TaskStatus -> TaskStatus -> Bool
== :: TaskStatus -> TaskStatus -> Bool
$c/= :: TaskStatus -> TaskStatus -> Bool
/= :: TaskStatus -> TaskStatus -> Bool
Eq, Typeable, Typeable TaskStatus
Typeable TaskStatus =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> TaskStatus -> c TaskStatus)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c TaskStatus)
-> (TaskStatus -> Constr)
-> (TaskStatus -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c TaskStatus))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c TaskStatus))
-> ((forall b. Data b => b -> b) -> TaskStatus -> TaskStatus)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> TaskStatus -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> TaskStatus -> r)
-> (forall u. (forall d. Data d => d -> u) -> TaskStatus -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> TaskStatus -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus)
-> Data TaskStatus
TaskStatus -> Constr
TaskStatus -> DataType
(forall b. Data b => b -> b) -> TaskStatus -> TaskStatus
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TaskStatus -> u
forall u. (forall d. Data d => d -> u) -> TaskStatus -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TaskStatus -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TaskStatus -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TaskStatus
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TaskStatus -> c TaskStatus
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TaskStatus)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaskStatus)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TaskStatus -> c TaskStatus
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TaskStatus -> c TaskStatus
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TaskStatus
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TaskStatus
$ctoConstr :: TaskStatus -> Constr
toConstr :: TaskStatus -> Constr
$cdataTypeOf :: TaskStatus -> DataType
dataTypeOf :: TaskStatus -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TaskStatus)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TaskStatus)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaskStatus)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaskStatus)
$cgmapT :: (forall b. Data b => b -> b) -> TaskStatus -> TaskStatus
gmapT :: (forall b. Data b => b -> b) -> TaskStatus -> TaskStatus
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TaskStatus -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TaskStatus -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TaskStatus -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TaskStatus -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TaskStatus -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TaskStatus -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TaskStatus -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TaskStatus -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TaskStatus -> m TaskStatus
Data, (forall x. TaskStatus -> Rep TaskStatus x)
-> (forall x. Rep TaskStatus x -> TaskStatus) -> Generic TaskStatus
forall x. Rep TaskStatus x -> TaskStatus
forall x. TaskStatus -> Rep TaskStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TaskStatus -> Rep TaskStatus x
from :: forall x. TaskStatus -> Rep TaskStatus x
$cto :: forall x. Rep TaskStatus x -> TaskStatus
to :: forall x. Rep TaskStatus x -> TaskStatus
Generic)

newtype Caption = Caption Blocks
  deriving (Int -> Caption -> ShowS
[Caption] -> ShowS
Caption -> String
(Int -> Caption -> ShowS)
-> (Caption -> String) -> ([Caption] -> ShowS) -> Show Caption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Caption -> ShowS
showsPrec :: Int -> Caption -> ShowS
$cshow :: Caption -> String
show :: Caption -> String
$cshowList :: [Caption] -> ShowS
showList :: [Caption] -> ShowS
Show, Eq Caption
Eq Caption =>
(Caption -> Caption -> Ordering)
-> (Caption -> Caption -> Bool)
-> (Caption -> Caption -> Bool)
-> (Caption -> Caption -> Bool)
-> (Caption -> Caption -> Bool)
-> (Caption -> Caption -> Caption)
-> (Caption -> Caption -> Caption)
-> Ord Caption
Caption -> Caption -> Bool
Caption -> Caption -> Ordering
Caption -> Caption -> Caption
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Caption -> Caption -> Ordering
compare :: Caption -> Caption -> Ordering
$c< :: Caption -> Caption -> Bool
< :: Caption -> Caption -> Bool
$c<= :: Caption -> Caption -> Bool
<= :: Caption -> Caption -> Bool
$c> :: Caption -> Caption -> Bool
> :: Caption -> Caption -> Bool
$c>= :: Caption -> Caption -> Bool
>= :: Caption -> Caption -> Bool
$cmax :: Caption -> Caption -> Caption
max :: Caption -> Caption -> Caption
$cmin :: Caption -> Caption -> Caption
min :: Caption -> Caption -> Caption
Ord, Caption -> Caption -> Bool
(Caption -> Caption -> Bool)
-> (Caption -> Caption -> Bool) -> Eq Caption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Caption -> Caption -> Bool
== :: Caption -> Caption -> Bool
$c/= :: Caption -> Caption -> Bool
/= :: Caption -> Caption -> Bool
Eq, Typeable, Typeable Caption
Typeable Caption =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Caption -> c Caption)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Caption)
-> (Caption -> Constr)
-> (Caption -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Caption))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption))
-> ((forall b. Data b => b -> b) -> Caption -> Caption)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Caption -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Caption -> r)
-> (forall u. (forall d. Data d => d -> u) -> Caption -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Caption -> m Caption)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Caption -> m Caption)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Caption -> m Caption)
-> Data Caption
Caption -> Constr
Caption -> DataType
(forall b. Data b => b -> b) -> Caption -> Caption
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u
forall u. (forall d. Data d => d -> u) -> Caption -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Caption -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Caption -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Caption
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Caption -> c Caption
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Caption)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Caption -> c Caption
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Caption -> c Caption
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Caption
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Caption
$ctoConstr :: Caption -> Constr
toConstr :: Caption -> Constr
$cdataTypeOf :: Caption -> DataType
dataTypeOf :: Caption -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Caption)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Caption)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Caption)
$cgmapT :: (forall b. Data b => b -> b) -> Caption -> Caption
gmapT :: (forall b. Data b => b -> b) -> Caption -> Caption
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Caption -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Caption -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Caption -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Caption -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Caption -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Caption -> m Caption
Data, (forall x. Caption -> Rep Caption x)
-> (forall x. Rep Caption x -> Caption) -> Generic Caption
forall x. Rep Caption x -> Caption
forall x. Caption -> Rep Caption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Caption -> Rep Caption x
from :: forall x. Caption -> Rep Caption x
$cto :: forall x. Rep Caption x -> Caption
to :: forall x. Rep Caption x -> Caption
Generic)

data Align = AlignLeft | AlignRight | AlignCenter | AlignDefault
  deriving (Int -> Align -> ShowS
[Align] -> ShowS
Align -> String
(Int -> Align -> ShowS)
-> (Align -> String) -> ([Align] -> ShowS) -> Show Align
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Align -> ShowS
showsPrec :: Int -> Align -> ShowS
$cshow :: Align -> String
show :: Align -> String
$cshowList :: [Align] -> ShowS
showList :: [Align] -> ShowS
Show, Eq Align
Eq Align =>
(Align -> Align -> Ordering)
-> (Align -> Align -> Bool)
-> (Align -> Align -> Bool)
-> (Align -> Align -> Bool)
-> (Align -> Align -> Bool)
-> (Align -> Align -> Align)
-> (Align -> Align -> Align)
-> Ord Align
Align -> Align -> Bool
Align -> Align -> Ordering
Align -> Align -> Align
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Align -> Align -> Ordering
compare :: Align -> Align -> Ordering
$c< :: Align -> Align -> Bool
< :: Align -> Align -> Bool
$c<= :: Align -> Align -> Bool
<= :: Align -> Align -> Bool
$c> :: Align -> Align -> Bool
> :: Align -> Align -> Bool
$c>= :: Align -> Align -> Bool
>= :: Align -> Align -> Bool
$cmax :: Align -> Align -> Align
max :: Align -> Align -> Align
$cmin :: Align -> Align -> Align
min :: Align -> Align -> Align
Ord, Align -> Align -> Bool
(Align -> Align -> Bool) -> (Align -> Align -> Bool) -> Eq Align
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Align -> Align -> Bool
== :: Align -> Align -> Bool
$c/= :: Align -> Align -> Bool
/= :: Align -> Align -> Bool
Eq, Typeable, Typeable Align
Typeable Align =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Align -> c Align)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Align)
-> (Align -> Constr)
-> (Align -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Align))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Align))
-> ((forall b. Data b => b -> b) -> Align -> Align)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r)
-> (forall u. (forall d. Data d => d -> u) -> Align -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Align -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Align -> m Align)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Align -> m Align)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Align -> m Align)
-> Data Align
Align -> Constr
Align -> DataType
(forall b. Data b => b -> b) -> Align -> Align
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Align -> u
forall u. (forall d. Data d => d -> u) -> Align -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Align -> m Align
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Align -> m Align
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Align
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Align -> c Align
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Align)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Align)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Align -> c Align
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Align -> c Align
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Align
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Align
$ctoConstr :: Align -> Constr
toConstr :: Align -> Constr
$cdataTypeOf :: Align -> DataType
dataTypeOf :: Align -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Align)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Align)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Align)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Align)
$cgmapT :: (forall b. Data b => b -> b) -> Align -> Align
gmapT :: (forall b. Data b => b -> b) -> Align -> Align
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Align -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Align -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Align -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Align -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Align -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Align -> m Align
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Align -> m Align
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Align -> m Align
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Align -> m Align
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Align -> m Align
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Align -> m Align
Data, (forall x. Align -> Rep Align x)
-> (forall x. Rep Align x -> Align) -> Generic Align
forall x. Rep Align x -> Align
forall x. Align -> Rep Align x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Align -> Rep Align x
from :: forall x. Align -> Rep Align x
$cto :: forall x. Rep Align x -> Align
to :: forall x. Rep Align x -> Align
Generic)

data CellType = HeadCell | BodyCell
  deriving (Int -> CellType -> ShowS
[CellType] -> ShowS
CellType -> String
(Int -> CellType -> ShowS)
-> (CellType -> String) -> ([CellType] -> ShowS) -> Show CellType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CellType -> ShowS
showsPrec :: Int -> CellType -> ShowS
$cshow :: CellType -> String
show :: CellType -> String
$cshowList :: [CellType] -> ShowS
showList :: [CellType] -> ShowS
Show, Eq CellType
Eq CellType =>
(CellType -> CellType -> Ordering)
-> (CellType -> CellType -> Bool)
-> (CellType -> CellType -> Bool)
-> (CellType -> CellType -> Bool)
-> (CellType -> CellType -> Bool)
-> (CellType -> CellType -> CellType)
-> (CellType -> CellType -> CellType)
-> Ord CellType
CellType -> CellType -> Bool
CellType -> CellType -> Ordering
CellType -> CellType -> CellType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CellType -> CellType -> Ordering
compare :: CellType -> CellType -> Ordering
$c< :: CellType -> CellType -> Bool
< :: CellType -> CellType -> Bool
$c<= :: CellType -> CellType -> Bool
<= :: CellType -> CellType -> Bool
$c> :: CellType -> CellType -> Bool
> :: CellType -> CellType -> Bool
$c>= :: CellType -> CellType -> Bool
>= :: CellType -> CellType -> Bool
$cmax :: CellType -> CellType -> CellType
max :: CellType -> CellType -> CellType
$cmin :: CellType -> CellType -> CellType
min :: CellType -> CellType -> CellType
Ord, CellType -> CellType -> Bool
(CellType -> CellType -> Bool)
-> (CellType -> CellType -> Bool) -> Eq CellType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CellType -> CellType -> Bool
== :: CellType -> CellType -> Bool
$c/= :: CellType -> CellType -> Bool
/= :: CellType -> CellType -> Bool
Eq, Typeable, Typeable CellType
Typeable CellType =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> CellType -> c CellType)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c CellType)
-> (CellType -> Constr)
-> (CellType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c CellType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellType))
-> ((forall b. Data b => b -> b) -> CellType -> CellType)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> CellType -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> CellType -> r)
-> (forall u. (forall d. Data d => d -> u) -> CellType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> CellType -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> CellType -> m CellType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> CellType -> m CellType)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> CellType -> m CellType)
-> Data CellType
CellType -> Constr
CellType -> DataType
(forall b. Data b => b -> b) -> CellType -> CellType
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CellType -> u
forall u. (forall d. Data d => d -> u) -> CellType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CellType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CellType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CellType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CellType -> c CellType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CellType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CellType -> c CellType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CellType -> c CellType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CellType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CellType
$ctoConstr :: CellType -> Constr
toConstr :: CellType -> Constr
$cdataTypeOf :: CellType -> DataType
dataTypeOf :: CellType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CellType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CellType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CellType)
$cgmapT :: (forall b. Data b => b -> b) -> CellType -> CellType
gmapT :: (forall b. Data b => b -> b) -> CellType -> CellType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CellType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CellType -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CellType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CellType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CellType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CellType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CellType -> m CellType
Data, (forall x. CellType -> Rep CellType x)
-> (forall x. Rep CellType x -> CellType) -> Generic CellType
forall x. Rep CellType x -> CellType
forall x. CellType -> Rep CellType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CellType -> Rep CellType x
from :: forall x. CellType -> Rep CellType x
$cto :: forall x. Rep CellType x -> CellType
to :: forall x. Rep CellType x -> CellType
Generic)

data Cell = Cell CellType Align Inlines
  deriving (Int -> Cell -> ShowS
[Cell] -> ShowS
Cell -> String
(Int -> Cell -> ShowS)
-> (Cell -> String) -> ([Cell] -> ShowS) -> Show Cell
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cell -> ShowS
showsPrec :: Int -> Cell -> ShowS
$cshow :: Cell -> String
show :: Cell -> String
$cshowList :: [Cell] -> ShowS
showList :: [Cell] -> ShowS
Show, Eq Cell
Eq Cell =>
(Cell -> Cell -> Ordering)
-> (Cell -> Cell -> Bool)
-> (Cell -> Cell -> Bool)
-> (Cell -> Cell -> Bool)
-> (Cell -> Cell -> Bool)
-> (Cell -> Cell -> Cell)
-> (Cell -> Cell -> Cell)
-> Ord Cell
Cell -> Cell -> Bool
Cell -> Cell -> Ordering
Cell -> Cell -> Cell
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Cell -> Cell -> Ordering
compare :: Cell -> Cell -> Ordering
$c< :: Cell -> Cell -> Bool
< :: Cell -> Cell -> Bool
$c<= :: Cell -> Cell -> Bool
<= :: Cell -> Cell -> Bool
$c> :: Cell -> Cell -> Bool
> :: Cell -> Cell -> Bool
$c>= :: Cell -> Cell -> Bool
>= :: Cell -> Cell -> Bool
$cmax :: Cell -> Cell -> Cell
max :: Cell -> Cell -> Cell
$cmin :: Cell -> Cell -> Cell
min :: Cell -> Cell -> Cell
Ord, Cell -> Cell -> Bool
(Cell -> Cell -> Bool) -> (Cell -> Cell -> Bool) -> Eq Cell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cell -> Cell -> Bool
== :: Cell -> Cell -> Bool
$c/= :: Cell -> Cell -> Bool
/= :: Cell -> Cell -> Bool
Eq, Typeable, Typeable Cell
Typeable Cell =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Cell -> c Cell)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Cell)
-> (Cell -> Constr)
-> (Cell -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Cell))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell))
-> ((forall b. Data b => b -> b) -> Cell -> Cell)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r)
-> (forall u. (forall d. Data d => d -> u) -> Cell -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Cell -> m Cell)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Cell -> m Cell)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Cell -> m Cell)
-> Data Cell
Cell -> Constr
Cell -> DataType
(forall b. Data b => b -> b) -> Cell -> Cell
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u
forall u. (forall d. Data d => d -> u) -> Cell -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cell
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cell -> c Cell
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cell)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cell -> c Cell
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cell -> c Cell
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cell
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cell
$ctoConstr :: Cell -> Constr
toConstr :: Cell -> Constr
$cdataTypeOf :: Cell -> DataType
dataTypeOf :: Cell -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cell)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cell)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell)
$cgmapT :: (forall b. Data b => b -> b) -> Cell -> Cell
gmapT :: (forall b. Data b => b -> b) -> Cell -> Cell
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Cell -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Cell -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
Data, (forall x. Cell -> Rep Cell x)
-> (forall x. Rep Cell x -> Cell) -> Generic Cell
forall x. Rep Cell x -> Cell
forall x. Cell -> Rep Cell x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Cell -> Rep Cell x
from :: forall x. Cell -> Rep Cell x
$cto :: forall x. Rep Cell x -> Cell
to :: forall x. Rep Cell x -> Cell
Generic)

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
  deriving (Int -> Block -> ShowS
[Block] -> ShowS
Block -> String
(Int -> Block -> ShowS)
-> (Block -> String) -> ([Block] -> ShowS) -> Show Block
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Block -> ShowS
showsPrec :: Int -> Block -> ShowS
$cshow :: Block -> String
show :: Block -> String
$cshowList :: [Block] -> ShowS
showList :: [Block] -> ShowS
Show, Eq Block
Eq Block =>
(Block -> Block -> Ordering)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Block)
-> (Block -> Block -> Block)
-> Ord Block
Block -> Block -> Bool
Block -> Block -> Ordering
Block -> Block -> Block
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Block -> Block -> Ordering
compare :: Block -> Block -> Ordering
$c< :: Block -> Block -> Bool
< :: Block -> Block -> Bool
$c<= :: Block -> Block -> Bool
<= :: Block -> Block -> Bool
$c> :: Block -> Block -> Bool
> :: Block -> Block -> Bool
$c>= :: Block -> Block -> Bool
>= :: Block -> Block -> Bool
$cmax :: Block -> Block -> Block
max :: Block -> Block -> Block
$cmin :: Block -> Block -> Block
min :: Block -> Block -> Block
Ord, Block -> Block -> Bool
(Block -> Block -> Bool) -> (Block -> Block -> Bool) -> Eq Block
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Block -> Block -> Bool
== :: Block -> Block -> Bool
$c/= :: Block -> Block -> Bool
/= :: Block -> Block -> Bool
Eq, Typeable, Typeable Block
Typeable Block =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Block -> c Block)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Block)
-> (Block -> Constr)
-> (Block -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Block))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block))
-> ((forall b. Data b => b -> b) -> Block -> Block)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r)
-> (forall u. (forall d. Data d => d -> u) -> Block -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Block -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Block -> m Block)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Block -> m Block)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Block -> m Block)
-> Data Block
Block -> Constr
Block -> DataType
(forall b. Data b => b -> b) -> Block -> Block
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Block -> u
forall u. (forall d. Data d => d -> u) -> Block -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Block -> m Block
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Block -> m Block
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Block
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Block -> c Block
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Block)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Block -> c Block
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Block -> c Block
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Block
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Block
$ctoConstr :: Block -> Constr
toConstr :: Block -> Constr
$cdataTypeOf :: Block -> DataType
dataTypeOf :: Block -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Block)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Block)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block)
$cgmapT :: (forall b. Data b => b -> b) -> Block -> Block
gmapT :: (forall b. Data b => b -> b) -> Block -> Block
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Block -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Block -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Block -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Block -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Block -> m Block
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Block -> m Block
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Block -> m Block
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Block -> m Block
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Block -> m Block
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Block -> m Block
Data, (forall x. Block -> Rep Block x)
-> (forall x. Rep Block x -> Block) -> Generic Block
forall x. Rep Block x -> Block
forall x. Block -> Rep Block x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Block -> Rep Block x
from :: forall x. Block -> Rep Block x
$cto :: forall x. Rep Block x -> Block
to :: forall x. Rep Block x -> Block
Generic)

type Blocks = Many (Node Block)

instance Semigroup Blocks where
  Many Seq (Node Block)
as <> :: Blocks -> Blocks -> Blocks
<> Many Seq (Node Block)
bs = Seq (Node Block) -> Blocks
forall a. Seq a -> Many a
Many (Seq (Node Block)
as Seq (Node Block) -> Seq (Node Block) -> Seq (Node Block)
forall a. Semigroup a => a -> a -> a
<> Seq (Node Block)
bs)

instance Monoid Blocks where
  mappend :: Blocks -> Blocks -> Blocks
mappend = Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: Blocks
mempty = Seq (Node Block) -> Blocks
forall a. Seq a -> Many a
Many Seq (Node Block)
forall a. Monoid a => a
mempty

data Doc =
  Doc{ Doc -> Blocks
docBlocks :: Blocks
     , Doc -> NoteMap
docFootnotes :: NoteMap
     , Doc -> ReferenceMap
docReferences :: ReferenceMap
     , Doc -> ReferenceMap
docAutoReferences :: ReferenceMap
     , Doc -> Set ByteString
docAutoIdentifiers :: Set ByteString
     } deriving (Int -> Doc -> ShowS
[Doc] -> ShowS
Doc -> String
(Int -> Doc -> ShowS)
-> (Doc -> String) -> ([Doc] -> ShowS) -> Show Doc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Doc -> ShowS
showsPrec :: Int -> Doc -> ShowS
$cshow :: Doc -> String
show :: Doc -> String
$cshowList :: [Doc] -> ShowS
showList :: [Doc] -> ShowS
Show, Eq Doc
Eq Doc =>
(Doc -> Doc -> Ordering)
-> (Doc -> Doc -> Bool)
-> (Doc -> Doc -> Bool)
-> (Doc -> Doc -> Bool)
-> (Doc -> Doc -> Bool)
-> (Doc -> Doc -> Doc)
-> (Doc -> Doc -> Doc)
-> Ord Doc
Doc -> Doc -> Bool
Doc -> Doc -> Ordering
Doc -> Doc -> Doc
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Doc -> Doc -> Ordering
compare :: Doc -> Doc -> Ordering
$c< :: Doc -> Doc -> Bool
< :: Doc -> Doc -> Bool
$c<= :: Doc -> Doc -> Bool
<= :: Doc -> Doc -> Bool
$c> :: Doc -> Doc -> Bool
> :: Doc -> Doc -> Bool
$c>= :: Doc -> Doc -> Bool
>= :: Doc -> Doc -> Bool
$cmax :: Doc -> Doc -> Doc
max :: Doc -> Doc -> Doc
$cmin :: Doc -> Doc -> Doc
min :: Doc -> Doc -> Doc
Ord, Doc -> Doc -> Bool
(Doc -> Doc -> Bool) -> (Doc -> Doc -> Bool) -> Eq Doc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Doc -> Doc -> Bool
== :: Doc -> Doc -> Bool
$c/= :: Doc -> Doc -> Bool
/= :: Doc -> Doc -> Bool
Eq, Typeable, Typeable Doc
Typeable Doc =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Doc -> c Doc)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Doc)
-> (Doc -> Constr)
-> (Doc -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Doc))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc))
-> ((forall b. Data b => b -> b) -> Doc -> Doc)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r)
-> (forall u. (forall d. Data d => d -> u) -> Doc -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Doc -> m Doc)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Doc -> m Doc)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Doc -> m Doc)
-> Data Doc
Doc -> Constr
Doc -> DataType
(forall b. Data b => b -> b) -> Doc -> Doc
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
forall u. (forall d. Data d => d -> u) -> Doc -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
$ctoConstr :: Doc -> Constr
toConstr :: Doc -> Constr
$cdataTypeOf :: Doc -> DataType
dataTypeOf :: Doc -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
$cgmapT :: (forall b. Data b => b -> b) -> Doc -> Doc
gmapT :: (forall b. Data b => b -> b) -> Doc -> Doc
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
Data, (forall x. Doc -> Rep Doc x)
-> (forall x. Rep Doc x -> Doc) -> Generic Doc
forall x. Rep Doc x -> Doc
forall x. Doc -> Rep Doc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Doc -> Rep Doc x
from :: forall x. Doc -> Rep Doc x
$cto :: forall x. Rep Doc x -> Doc
to :: forall x. Rep Doc x -> Doc
Generic)

instance Semigroup Doc where
  Doc Blocks
bs NoteMap
ns ReferenceMap
rs ReferenceMap
ar Set ByteString
ai <> :: Doc -> Doc -> Doc
<> Doc Blocks
bs' NoteMap
ns' ReferenceMap
rs' ReferenceMap
ar' Set ByteString
ai' =
    Blocks
-> NoteMap -> ReferenceMap -> ReferenceMap -> Set ByteString -> Doc
Doc (Blocks
bs Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
bs') (NoteMap
ns NoteMap -> NoteMap -> NoteMap
forall a. Semigroup a => a -> a -> a
<> NoteMap
ns') (ReferenceMap
rs ReferenceMap -> ReferenceMap -> ReferenceMap
forall a. Semigroup a => a -> a -> a
<> ReferenceMap
rs') (ReferenceMap
ar ReferenceMap -> ReferenceMap -> ReferenceMap
forall a. Semigroup a => a -> a -> a
<> ReferenceMap
ar') (Set ByteString
ai Set ByteString -> Set ByteString -> Set ByteString
forall a. Semigroup a => a -> a -> a
<> Set ByteString
ai')

instance Monoid Doc where
  mappend :: Doc -> Doc -> Doc
mappend = Doc -> Doc -> Doc
forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: Doc
mempty = Blocks
-> NoteMap -> ReferenceMap -> ReferenceMap -> Set ByteString -> Doc
Doc Blocks
forall a. Monoid a => a
mempty NoteMap
forall a. Monoid a => a
mempty ReferenceMap
forall a. Monoid a => a
mempty ReferenceMap
forall a. Monoid a => a
mempty Set ByteString
forall a. Monoid a => a
mempty

-- | A map from labels to contents.
newtype NoteMap = NoteMap { NoteMap -> Map ByteString Blocks
unNoteMap :: M.Map ByteString Blocks }
  deriving (Int -> NoteMap -> ShowS
[NoteMap] -> ShowS
NoteMap -> String
(Int -> NoteMap -> ShowS)
-> (NoteMap -> String) -> ([NoteMap] -> ShowS) -> Show NoteMap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NoteMap -> ShowS
showsPrec :: Int -> NoteMap -> ShowS
$cshow :: NoteMap -> String
show :: NoteMap -> String
$cshowList :: [NoteMap] -> ShowS
showList :: [NoteMap] -> ShowS
Show, Eq NoteMap
Eq NoteMap =>
(NoteMap -> NoteMap -> Ordering)
-> (NoteMap -> NoteMap -> Bool)
-> (NoteMap -> NoteMap -> Bool)
-> (NoteMap -> NoteMap -> Bool)
-> (NoteMap -> NoteMap -> Bool)
-> (NoteMap -> NoteMap -> NoteMap)
-> (NoteMap -> NoteMap -> NoteMap)
-> Ord NoteMap
NoteMap -> NoteMap -> Bool
NoteMap -> NoteMap -> Ordering
NoteMap -> NoteMap -> NoteMap
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NoteMap -> NoteMap -> Ordering
compare :: NoteMap -> NoteMap -> Ordering
$c< :: NoteMap -> NoteMap -> Bool
< :: NoteMap -> NoteMap -> Bool
$c<= :: NoteMap -> NoteMap -> Bool
<= :: NoteMap -> NoteMap -> Bool
$c> :: NoteMap -> NoteMap -> Bool
> :: NoteMap -> NoteMap -> Bool
$c>= :: NoteMap -> NoteMap -> Bool
>= :: NoteMap -> NoteMap -> Bool
$cmax :: NoteMap -> NoteMap -> NoteMap
max :: NoteMap -> NoteMap -> NoteMap
$cmin :: NoteMap -> NoteMap -> NoteMap
min :: NoteMap -> NoteMap -> NoteMap
Ord, NoteMap -> NoteMap -> Bool
(NoteMap -> NoteMap -> Bool)
-> (NoteMap -> NoteMap -> Bool) -> Eq NoteMap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NoteMap -> NoteMap -> Bool
== :: NoteMap -> NoteMap -> Bool
$c/= :: NoteMap -> NoteMap -> Bool
/= :: NoteMap -> NoteMap -> Bool
Eq, NonEmpty NoteMap -> NoteMap
NoteMap -> NoteMap -> NoteMap
(NoteMap -> NoteMap -> NoteMap)
-> (NonEmpty NoteMap -> NoteMap)
-> (forall b. Integral b => b -> NoteMap -> NoteMap)
-> Semigroup NoteMap
forall b. Integral b => b -> NoteMap -> NoteMap
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: NoteMap -> NoteMap -> NoteMap
<> :: NoteMap -> NoteMap -> NoteMap
$csconcat :: NonEmpty NoteMap -> NoteMap
sconcat :: NonEmpty NoteMap -> NoteMap
$cstimes :: forall b. Integral b => b -> NoteMap -> NoteMap
stimes :: forall b. Integral b => b -> NoteMap -> NoteMap
Semigroup, Semigroup NoteMap
NoteMap
Semigroup NoteMap =>
NoteMap
-> (NoteMap -> NoteMap -> NoteMap)
-> ([NoteMap] -> NoteMap)
-> Monoid NoteMap
[NoteMap] -> NoteMap
NoteMap -> NoteMap -> NoteMap
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: NoteMap
mempty :: NoteMap
$cmappend :: NoteMap -> NoteMap -> NoteMap
mappend :: NoteMap -> NoteMap -> NoteMap
$cmconcat :: [NoteMap] -> NoteMap
mconcat :: [NoteMap] -> NoteMap
Monoid, Typeable, Typeable NoteMap
Typeable NoteMap =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> NoteMap -> c NoteMap)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c NoteMap)
-> (NoteMap -> Constr)
-> (NoteMap -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c NoteMap))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoteMap))
-> ((forall b. Data b => b -> b) -> NoteMap -> NoteMap)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> NoteMap -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> NoteMap -> r)
-> (forall u. (forall d. Data d => d -> u) -> NoteMap -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> NoteMap -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> NoteMap -> m NoteMap)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NoteMap -> m NoteMap)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> NoteMap -> m NoteMap)
-> Data NoteMap
NoteMap -> Constr
NoteMap -> DataType
(forall b. Data b => b -> b) -> NoteMap -> NoteMap
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> NoteMap -> u
forall u. (forall d. Data d => d -> u) -> NoteMap -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoteMap -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NoteMap -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoteMap
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoteMap -> c NoteMap
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoteMap)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoteMap)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoteMap -> c NoteMap
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoteMap -> c NoteMap
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoteMap
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoteMap
$ctoConstr :: NoteMap -> Constr
toConstr :: NoteMap -> Constr
$cdataTypeOf :: NoteMap -> DataType
dataTypeOf :: NoteMap -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoteMap)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoteMap)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoteMap)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoteMap)
$cgmapT :: (forall b. Data b => b -> b) -> NoteMap -> NoteMap
gmapT :: (forall b. Data b => b -> b) -> NoteMap -> NoteMap
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoteMap -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoteMap -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NoteMap -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NoteMap -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NoteMap -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NoteMap -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoteMap -> m NoteMap
Data, (forall x. NoteMap -> Rep NoteMap x)
-> (forall x. Rep NoteMap x -> NoteMap) -> Generic NoteMap
forall x. Rep NoteMap x -> NoteMap
forall x. NoteMap -> Rep NoteMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NoteMap -> Rep NoteMap x
from :: forall x. NoteMap -> Rep NoteMap x
$cto :: forall x. Rep NoteMap x -> NoteMap
to :: forall x. Rep NoteMap x -> NoteMap
Generic)

insertNote :: ByteString -> Blocks -> NoteMap -> NoteMap
insertNote :: ByteString -> Blocks -> NoteMap -> NoteMap
insertNote ByteString
label Blocks
ref (NoteMap Map ByteString Blocks
m) =
  Map ByteString Blocks -> NoteMap
NoteMap (ByteString
-> Blocks -> Map ByteString Blocks -> Map ByteString Blocks
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (ByteString -> ByteString
normalizeLabel ByteString
label) Blocks
ref Map ByteString Blocks
m)

lookupNote :: ByteString -> NoteMap -> Maybe Blocks
lookupNote :: ByteString -> NoteMap -> Maybe Blocks
lookupNote ByteString
label (NoteMap Map ByteString Blocks
m) =
  ByteString -> Map ByteString Blocks -> Maybe Blocks
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ByteString -> ByteString
normalizeLabel ByteString
label) Map ByteString Blocks
m

newtype ReferenceMap =
  ReferenceMap { ReferenceMap -> Map ByteString (ByteString, Attr)
unReferenceMap :: M.Map ByteString (ByteString, Attr) }
  deriving (Int -> ReferenceMap -> ShowS
[ReferenceMap] -> ShowS
ReferenceMap -> String
(Int -> ReferenceMap -> ShowS)
-> (ReferenceMap -> String)
-> ([ReferenceMap] -> ShowS)
-> Show ReferenceMap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReferenceMap -> ShowS
showsPrec :: Int -> ReferenceMap -> ShowS
$cshow :: ReferenceMap -> String
show :: ReferenceMap -> String
$cshowList :: [ReferenceMap] -> ShowS
showList :: [ReferenceMap] -> ShowS
Show, Eq ReferenceMap
Eq ReferenceMap =>
(ReferenceMap -> ReferenceMap -> Ordering)
-> (ReferenceMap -> ReferenceMap -> Bool)
-> (ReferenceMap -> ReferenceMap -> Bool)
-> (ReferenceMap -> ReferenceMap -> Bool)
-> (ReferenceMap -> ReferenceMap -> Bool)
-> (ReferenceMap -> ReferenceMap -> ReferenceMap)
-> (ReferenceMap -> ReferenceMap -> ReferenceMap)
-> Ord ReferenceMap
ReferenceMap -> ReferenceMap -> Bool
ReferenceMap -> ReferenceMap -> Ordering
ReferenceMap -> ReferenceMap -> ReferenceMap
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ReferenceMap -> ReferenceMap -> Ordering
compare :: ReferenceMap -> ReferenceMap -> Ordering
$c< :: ReferenceMap -> ReferenceMap -> Bool
< :: ReferenceMap -> ReferenceMap -> Bool
$c<= :: ReferenceMap -> ReferenceMap -> Bool
<= :: ReferenceMap -> ReferenceMap -> Bool
$c> :: ReferenceMap -> ReferenceMap -> Bool
> :: ReferenceMap -> ReferenceMap -> Bool
$c>= :: ReferenceMap -> ReferenceMap -> Bool
>= :: ReferenceMap -> ReferenceMap -> Bool
$cmax :: ReferenceMap -> ReferenceMap -> ReferenceMap
max :: ReferenceMap -> ReferenceMap -> ReferenceMap
$cmin :: ReferenceMap -> ReferenceMap -> ReferenceMap
min :: ReferenceMap -> ReferenceMap -> ReferenceMap
Ord, ReferenceMap -> ReferenceMap -> Bool
(ReferenceMap -> ReferenceMap -> Bool)
-> (ReferenceMap -> ReferenceMap -> Bool) -> Eq ReferenceMap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReferenceMap -> ReferenceMap -> Bool
== :: ReferenceMap -> ReferenceMap -> Bool
$c/= :: ReferenceMap -> ReferenceMap -> Bool
/= :: ReferenceMap -> ReferenceMap -> Bool
Eq, NonEmpty ReferenceMap -> ReferenceMap
ReferenceMap -> ReferenceMap -> ReferenceMap
(ReferenceMap -> ReferenceMap -> ReferenceMap)
-> (NonEmpty ReferenceMap -> ReferenceMap)
-> (forall b. Integral b => b -> ReferenceMap -> ReferenceMap)
-> Semigroup ReferenceMap
forall b. Integral b => b -> ReferenceMap -> ReferenceMap
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: ReferenceMap -> ReferenceMap -> ReferenceMap
<> :: ReferenceMap -> ReferenceMap -> ReferenceMap
$csconcat :: NonEmpty ReferenceMap -> ReferenceMap
sconcat :: NonEmpty ReferenceMap -> ReferenceMap
$cstimes :: forall b. Integral b => b -> ReferenceMap -> ReferenceMap
stimes :: forall b. Integral b => b -> ReferenceMap -> ReferenceMap
Semigroup, Semigroup ReferenceMap
ReferenceMap
Semigroup ReferenceMap =>
ReferenceMap
-> (ReferenceMap -> ReferenceMap -> ReferenceMap)
-> ([ReferenceMap] -> ReferenceMap)
-> Monoid ReferenceMap
[ReferenceMap] -> ReferenceMap
ReferenceMap -> ReferenceMap -> ReferenceMap
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: ReferenceMap
mempty :: ReferenceMap
$cmappend :: ReferenceMap -> ReferenceMap -> ReferenceMap
mappend :: ReferenceMap -> ReferenceMap -> ReferenceMap
$cmconcat :: [ReferenceMap] -> ReferenceMap
mconcat :: [ReferenceMap] -> ReferenceMap
Monoid, Typeable, Typeable ReferenceMap
Typeable ReferenceMap =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ReferenceMap -> c ReferenceMap)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ReferenceMap)
-> (ReferenceMap -> Constr)
-> (ReferenceMap -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ReferenceMap))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c ReferenceMap))
-> ((forall b. Data b => b -> b) -> ReferenceMap -> ReferenceMap)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r)
-> (forall u. (forall d. Data d => d -> u) -> ReferenceMap -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ReferenceMap -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap)
-> Data ReferenceMap
ReferenceMap -> Constr
ReferenceMap -> DataType
(forall b. Data b => b -> b) -> ReferenceMap -> ReferenceMap
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ReferenceMap -> u
forall u. (forall d. Data d => d -> u) -> ReferenceMap -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceMap
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceMap -> c ReferenceMap
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceMap)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceMap)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceMap -> c ReferenceMap
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ReferenceMap -> c ReferenceMap
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceMap
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ReferenceMap
$ctoConstr :: ReferenceMap -> Constr
toConstr :: ReferenceMap -> Constr
$cdataTypeOf :: ReferenceMap -> DataType
dataTypeOf :: ReferenceMap -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceMap)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ReferenceMap)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceMap)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ReferenceMap)
$cgmapT :: (forall b. Data b => b -> b) -> ReferenceMap -> ReferenceMap
gmapT :: (forall b. Data b => b -> b) -> ReferenceMap -> ReferenceMap
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ReferenceMap -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ReferenceMap -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ReferenceMap -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReferenceMap -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ReferenceMap -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ReferenceMap -> m ReferenceMap
Data, (forall x. ReferenceMap -> Rep ReferenceMap x)
-> (forall x. Rep ReferenceMap x -> ReferenceMap)
-> Generic ReferenceMap
forall x. Rep ReferenceMap x -> ReferenceMap
forall x. ReferenceMap -> Rep ReferenceMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReferenceMap -> Rep ReferenceMap x
from :: forall x. ReferenceMap -> Rep ReferenceMap x
$cto :: forall x. Rep ReferenceMap x -> ReferenceMap
to :: forall x. Rep ReferenceMap x -> ReferenceMap
Generic)

normalizeLabel :: ByteString -> ByteString
normalizeLabel :: ByteString -> ByteString
normalizeLabel = [ByteString] -> ByteString
B8.unwords ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ByteString -> [ByteString]
B8.splitWith Char -> Bool
isWs
 where
  isWs :: Char -> Bool
isWs Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\r' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n'

insertReference :: ByteString -> (ByteString, Attr) -> ReferenceMap
                -> ReferenceMap
insertReference :: ByteString -> (ByteString, Attr) -> ReferenceMap -> ReferenceMap
insertReference ByteString
label (ByteString, Attr)
ref (ReferenceMap Map ByteString (ByteString, Attr)
rm) =
  Map ByteString (ByteString, Attr) -> ReferenceMap
ReferenceMap (ByteString
-> (ByteString, Attr)
-> Map ByteString (ByteString, Attr)
-> Map ByteString (ByteString, Attr)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (ByteString -> ByteString
normalizeLabel ByteString
label) (ByteString, Attr)
ref Map ByteString (ByteString, Attr)
rm)

lookupReference :: ByteString -> ReferenceMap -> Maybe (ByteString, Attr)
lookupReference :: ByteString -> ReferenceMap -> Maybe (ByteString, Attr)
lookupReference ByteString
label (ReferenceMap Map ByteString (ByteString, Attr)
rm) =
  ByteString
-> Map ByteString (ByteString, Attr) -> Maybe (ByteString, Attr)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (ByteString -> ByteString
normalizeLabel ByteString
label) Map ByteString (ByteString, Attr)
rm

{-# INLINE inline #-}
inline :: Inline -> Inlines
inline :: Inline -> Inlines
inline = Seq (Node Inline) -> Inlines
forall a. Seq a -> Many a
Many (Seq (Node Inline) -> Inlines)
-> (Inline -> Seq (Node Inline)) -> Inline -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node Inline -> Seq (Node Inline)
forall a. a -> Seq a
Seq.singleton (Node Inline -> Seq (Node Inline))
-> (Inline -> Node Inline) -> Inline -> Seq (Node Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pos -> Attr -> Inline -> Node Inline
forall a. Pos -> Attr -> a -> Node a
Node Pos
NoPos Attr
forall a. Monoid a => a
mempty

str, verbatim, symbol :: ByteString -> Inlines
str :: ByteString -> Inlines
str = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Inline
Str
verbatim :: ByteString -> Inlines
verbatim = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Inline
Verbatim
symbol :: ByteString -> Inlines
symbol = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Inline
Symbol

emph, strong, superscript, subscript :: Inlines -> Inlines
emph :: Inlines -> Inlines
emph = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Emph
strong :: Inlines -> Inlines
strong = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Strong
superscript :: Inlines -> Inlines
superscript = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Superscript
subscript :: Inlines -> Inlines
subscript = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Subscript

highlight, insert, delete :: Inlines -> Inlines
highlight :: Inlines -> Inlines
highlight = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Highlight
insert :: Inlines -> Inlines
insert = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Insert
delete :: Inlines -> Inlines
delete = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Delete

link, image :: Inlines -> Target -> Inlines
link :: Inlines -> Target -> Inlines
link Inlines
ils Target
url = Inline -> Inlines
inline (Inline -> Inlines) -> Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Target -> Inline
Link Inlines
ils Target
url
image :: Inlines -> Target -> Inlines
image Inlines
ils Target
url = Inline -> Inlines
inline (Inline -> Inlines) -> Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Target -> Inline
Image Inlines
ils Target
url

span_ :: Inlines -> Inlines
span_ :: Inlines -> Inlines
span_ = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inline
Span

softBreak, hardBreak, nonBreakingSpace :: Inlines
softBreak :: Inlines
softBreak = Inline -> Inlines
inline Inline
SoftBreak
hardBreak :: Inlines
hardBreak = Inline -> Inlines
inline Inline
HardBreak
nonBreakingSpace :: Inlines
nonBreakingSpace = Inline -> Inlines
inline Inline
NonBreakingSpace

inlineMath, displayMath :: ByteString -> Inlines
inlineMath :: ByteString -> Inlines
inlineMath = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MathStyle -> ByteString -> Inline
Math MathStyle
InlineMath
displayMath :: ByteString -> Inlines
displayMath = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MathStyle -> ByteString -> Inline
Math MathStyle
DisplayMath

singleQuoted, doubleQuoted :: Inlines -> Inlines
singleQuoted :: Inlines -> Inlines
singleQuoted = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuoteType -> Inlines -> Inline
Quoted QuoteType
SingleQuotes
doubleQuoted :: Inlines -> Inlines
doubleQuoted = Inline -> Inlines
inline (Inline -> Inlines) -> (Inlines -> Inline) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuoteType -> Inlines -> Inline
Quoted QuoteType
DoubleQuotes

footnoteReference :: ByteString -> Inlines
footnoteReference :: ByteString -> Inlines
footnoteReference = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Inline
FootnoteReference

urlLink, emailLink :: ByteString -> Inlines
urlLink :: ByteString -> Inlines
urlLink = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Inline
UrlLink
emailLink :: ByteString -> Inlines
emailLink = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Inline
EmailLink

rawInline :: Format -> ByteString -> Inlines
rawInline :: Format -> ByteString -> Inlines
rawInline Format
f = Inline -> Inlines
inline (Inline -> Inlines)
-> (ByteString -> Inline) -> ByteString -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> ByteString -> Inline
RawInline Format
f


--

block :: Block -> Blocks
block :: Block -> Blocks
block = Seq (Node Block) -> Blocks
forall a. Seq a -> Many a
Many (Seq (Node Block) -> Blocks)
-> (Block -> Seq (Node Block)) -> Block -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node Block -> Seq (Node Block)
forall a. a -> Seq a
Seq.singleton (Node Block -> Seq (Node Block))
-> (Block -> Node Block) -> Block -> Seq (Node Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pos -> Attr -> Block -> Node Block
forall a. Pos -> Attr -> a -> Node a
Node Pos
NoPos Attr
forall a. Monoid a => a
mempty

para :: Inlines -> Blocks
para :: Inlines -> Blocks
para = Block -> Blocks
block (Block -> Blocks) -> (Inlines -> Block) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Block
Para

section :: Blocks -> Blocks
section :: Blocks -> Blocks
section = Block -> Blocks
block (Block -> Blocks) -> (Blocks -> Block) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Block
Section

heading :: Int -> Inlines -> Blocks
heading :: Int -> Inlines -> Blocks
heading Int
lev = Block -> Blocks
block (Block -> Blocks) -> (Inlines -> Block) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Inlines -> Block
Heading Int
lev

blockQuote :: Blocks -> Blocks
blockQuote :: Blocks -> Blocks
blockQuote = Block -> Blocks
block (Block -> Blocks) -> (Blocks -> Block) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Block
BlockQuote

codeBlock :: ByteString -> ByteString -> Blocks
codeBlock :: ByteString -> ByteString -> Blocks
codeBlock ByteString
lang ByteString
bs = Block -> Blocks
block (Block -> Blocks) -> Block -> Blocks
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> Block
CodeBlock ByteString
lang ByteString
bs

bulletList :: ListSpacing -> [Blocks] -> Blocks
bulletList :: ListSpacing -> [Blocks] -> Blocks
bulletList ListSpacing
tightness = Block -> Blocks
block (Block -> Blocks) -> ([Blocks] -> Block) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListSpacing -> [Blocks] -> Block
BulletList ListSpacing
tightness

orderedList :: OrderedListAttributes -> ListSpacing -> [Blocks] -> Blocks
orderedList :: OrderedListAttributes -> ListSpacing -> [Blocks] -> Blocks
orderedList OrderedListAttributes
attr ListSpacing
tightness = Block -> Blocks
block (Block -> Blocks) -> ([Blocks] -> Block) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrderedListAttributes -> ListSpacing -> [Blocks] -> Block
OrderedList OrderedListAttributes
attr ListSpacing
tightness

definitionList :: ListSpacing -> [(Inlines, Blocks)] -> Blocks
definitionList :: ListSpacing -> [(Inlines, Blocks)] -> Blocks
definitionList ListSpacing
tightness = Block -> Blocks
block (Block -> Blocks)
-> ([(Inlines, Blocks)] -> Block) -> [(Inlines, Blocks)] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListSpacing -> [(Inlines, Blocks)] -> Block
DefinitionList ListSpacing
tightness

taskList :: ListSpacing -> [(TaskStatus, Blocks)] -> Blocks
taskList :: ListSpacing -> [(TaskStatus, Blocks)] -> Blocks
taskList ListSpacing
tightness = Block -> Blocks
block (Block -> Blocks)
-> ([(TaskStatus, Blocks)] -> Block)
-> [(TaskStatus, Blocks)]
-> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListSpacing -> [(TaskStatus, Blocks)] -> Block
TaskList ListSpacing
tightness

div :: Blocks -> Blocks
div :: Blocks -> Blocks
div = Block -> Blocks
block (Block -> Blocks) -> (Blocks -> Block) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Block
Div

thematicBreak :: Blocks
thematicBreak :: Blocks
thematicBreak = Block -> Blocks
block Block
ThematicBreak

table :: Maybe Caption -> [[Cell]] -> Blocks
table :: Maybe Caption -> [[Cell]] -> Blocks
table Maybe Caption
mbCaption = Block -> Blocks
block (Block -> Blocks) -> ([[Cell]] -> Block) -> [[Cell]] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Caption -> [[Cell]] -> Block
Table Maybe Caption
mbCaption

rawBlock :: Format -> ByteString -> Blocks
rawBlock :: Format -> ByteString -> Blocks
rawBlock Format
f = Block -> Blocks
block (Block -> Blocks) -> (ByteString -> Block) -> ByteString -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> ByteString -> Block
RawBlock Format
f

inlinesToByteString :: Inlines -> ByteString
inlinesToByteString :: Inlines -> ByteString
inlinesToByteString = (Node Inline -> ByteString) -> Seq (Node Inline) -> ByteString
forall m a. Monoid m => (a -> m) -> Seq a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Node Inline -> ByteString
go (Seq (Node Inline) -> ByteString)
-> (Inlines -> Seq (Node Inline)) -> Inlines -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Seq (Node Inline)
forall a. Many a -> Seq a
unMany
 where
  go :: Node Inline -> ByteString
go (Node Pos
_pos Attr
_attr Inline
x) =
      case Inline
x of
        Str ByteString
bs -> ByteString
bs
        Emph Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Strong Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Highlight Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Insert Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Delete Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Superscript Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Subscript Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Quoted QuoteType
SingleQuotes Inlines
ils ->
          ByteString
"\x2018" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Inlines -> ByteString
inlinesToByteString Inlines
ils ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"\x2019"
        Quoted QuoteType
DoubleQuotes Inlines
ils ->
          ByteString
"\x201C" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Inlines -> ByteString
inlinesToByteString Inlines
ils ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"\x201D"
        Verbatim ByteString
bs -> ByteString
bs
        Math MathStyle
DisplayMath ByteString
bs -> ByteString
"$$" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"$$"
        Math MathStyle
InlineMath ByteString
bs -> ByteString
"$" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"$"
        Symbol ByteString
bs -> ByteString
":" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
":"
        Link Inlines
ils Target
_url -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Image Inlines
ils Target
_url -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        Span Inlines
ils -> Inlines -> ByteString
inlinesToByteString Inlines
ils
        UrlLink ByteString
url -> ByteString
url
        EmailLink ByteString
email -> ByteString
email
        RawInline Format
_ ByteString
_ -> ByteString
forall a. Monoid a => a
mempty
        FootnoteReference ByteString
bs -> ByteString
"[" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
bs ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"]"
        Inline
SoftBreak -> ByteString
"\n"
        Inline
HardBreak -> ByteString
"\n"
        Inline
NonBreakingSpace -> ByteString
"\160"