{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Text.Pandoc.Z.Definition where
import Control.Lens
( view,
from,
iso,
prism',
review,
_Wrapped,
At(..),
Index,
IxValue,
Ixed(..),
Each(..),
AsEmpty(..),
Plated(..),
Iso',
Lens',
Prism',
Rewrapped,
Wrapped(..) )
import Data.Data(Data)
import Data.Stringz(HasText(text))
import Data.Typeable(Typeable)
import Data.Map(Map)
import qualified Data.Map as Map(map, union)
import Data.Text(Text)
import GHC.Generics(Generic)
import qualified Text.Pandoc.Definition as D
import Text.Pandoc.Walk(Walkable(walkM, query))
import Prelude hiding (div, span)
data Pandoc =
Pandoc
Meta
[Block]
deriving (Pandoc -> Pandoc -> Bool
(Pandoc -> Pandoc -> Bool)
-> (Pandoc -> Pandoc -> Bool) -> Eq Pandoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pandoc -> Pandoc -> Bool
== :: Pandoc -> Pandoc -> Bool
$c/= :: Pandoc -> Pandoc -> Bool
/= :: Pandoc -> Pandoc -> Bool
Eq, Eq Pandoc
Eq Pandoc =>
(Pandoc -> Pandoc -> Ordering)
-> (Pandoc -> Pandoc -> Bool)
-> (Pandoc -> Pandoc -> Bool)
-> (Pandoc -> Pandoc -> Bool)
-> (Pandoc -> Pandoc -> Bool)
-> (Pandoc -> Pandoc -> Pandoc)
-> (Pandoc -> Pandoc -> Pandoc)
-> Ord Pandoc
Pandoc -> Pandoc -> Bool
Pandoc -> Pandoc -> Ordering
Pandoc -> Pandoc -> Pandoc
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 :: Pandoc -> Pandoc -> Ordering
compare :: Pandoc -> Pandoc -> Ordering
$c< :: Pandoc -> Pandoc -> Bool
< :: Pandoc -> Pandoc -> Bool
$c<= :: Pandoc -> Pandoc -> Bool
<= :: Pandoc -> Pandoc -> Bool
$c> :: Pandoc -> Pandoc -> Bool
> :: Pandoc -> Pandoc -> Bool
$c>= :: Pandoc -> Pandoc -> Bool
>= :: Pandoc -> Pandoc -> Bool
$cmax :: Pandoc -> Pandoc -> Pandoc
max :: Pandoc -> Pandoc -> Pandoc
$cmin :: Pandoc -> Pandoc -> Pandoc
min :: Pandoc -> Pandoc -> Pandoc
Ord, Int -> Pandoc -> ShowS
[Pandoc] -> ShowS
Pandoc -> String
(Int -> Pandoc -> ShowS)
-> (Pandoc -> String) -> ([Pandoc] -> ShowS) -> Show Pandoc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pandoc -> ShowS
showsPrec :: Int -> Pandoc -> ShowS
$cshow :: Pandoc -> String
show :: Pandoc -> String
$cshowList :: [Pandoc] -> ShowS
showList :: [Pandoc] -> ShowS
Show, Typeable Pandoc
Typeable Pandoc =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pandoc -> c Pandoc)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pandoc)
-> (Pandoc -> Constr)
-> (Pandoc -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pandoc))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc))
-> ((forall b. Data b => b -> b) -> Pandoc -> Pandoc)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Pandoc -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Pandoc -> r)
-> (forall u. (forall d. Data d => d -> u) -> Pandoc -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Pandoc -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc)
-> Data Pandoc
Pandoc -> Constr
Pandoc -> DataType
(forall b. Data b => b -> b) -> Pandoc -> Pandoc
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) -> Pandoc -> u
forall u. (forall d. Data d => d -> u) -> Pandoc -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pandoc
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pandoc -> c Pandoc
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pandoc)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pandoc -> c Pandoc
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Pandoc -> c Pandoc
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pandoc
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Pandoc
$ctoConstr :: Pandoc -> Constr
toConstr :: Pandoc -> Constr
$cdataTypeOf :: Pandoc -> DataType
dataTypeOf :: Pandoc -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pandoc)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Pandoc)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pandoc)
$cgmapT :: (forall b. Data b => b -> b) -> Pandoc -> Pandoc
gmapT :: (forall b. Data b => b -> b) -> Pandoc -> Pandoc
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pandoc -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Pandoc -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Pandoc -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pandoc -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Pandoc -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Pandoc -> m Pandoc
Data, Typeable, ReadPrec [Pandoc]
ReadPrec Pandoc
Int -> ReadS Pandoc
ReadS [Pandoc]
(Int -> ReadS Pandoc)
-> ReadS [Pandoc]
-> ReadPrec Pandoc
-> ReadPrec [Pandoc]
-> Read Pandoc
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pandoc
readsPrec :: Int -> ReadS Pandoc
$creadList :: ReadS [Pandoc]
readList :: ReadS [Pandoc]
$creadPrec :: ReadPrec Pandoc
readPrec :: ReadPrec Pandoc
$creadListPrec :: ReadPrec [Pandoc]
readListPrec :: ReadPrec [Pandoc]
Read, (forall x. Pandoc -> Rep Pandoc x)
-> (forall x. Rep Pandoc x -> Pandoc) -> Generic Pandoc
forall x. Rep Pandoc x -> Pandoc
forall x. Pandoc -> Rep Pandoc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Pandoc -> Rep Pandoc x
from :: forall x. Pandoc -> Rep Pandoc x
$cto :: forall x. Rep Pandoc x -> Pandoc
to :: forall x. Rep Pandoc x -> Pandoc
Generic)
class HasPandoc a where
pandoc ::
Lens' a Pandoc
instance HasPandoc Pandoc where
pandoc :: Lens' Pandoc Pandoc
pandoc =
(Pandoc -> f Pandoc) -> Pandoc -> f Pandoc
forall a. a -> a
id
instance HasBlocks Pandoc where
blocks :: Lens' Pandoc [Block]
blocks [Block] -> f [Block]
f (Pandoc Meta
m [Block]
b) =
([Block] -> Pandoc) -> f [Block] -> f Pandoc
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Meta -> [Block] -> Pandoc
Pandoc Meta
m) ([Block] -> f [Block]
f [Block]
b)
instance HasPandoc D.Pandoc where
pandoc :: Lens' Pandoc Pandoc
pandoc =
AnIso Pandoc Pandoc Pandoc Pandoc
-> Iso Pandoc Pandoc Pandoc Pandoc
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Pandoc Pandoc Pandoc Pandoc
Iso' Pandoc Pandoc
isPandoc
instance HasMeta Pandoc where
meta :: Lens' Pandoc Meta
meta Meta -> f Meta
f (Pandoc Meta
m [Block]
b) =
(Meta -> Pandoc) -> f Meta -> f Pandoc
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Meta -> [Block] -> Pandoc
`Pandoc` [Block]
b) (Meta -> f Meta
f Meta
m)
instance HasMeta D.Pandoc where
meta :: Lens' Pandoc Meta
meta =
AnIso Pandoc Pandoc Pandoc Pandoc
-> Iso Pandoc Pandoc Pandoc Pandoc
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Pandoc Pandoc Pandoc Pandoc
Iso' Pandoc Pandoc
isPandoc ((Pandoc -> f Pandoc) -> Pandoc -> f Pandoc)
-> ((Meta -> f Meta) -> Pandoc -> f Pandoc)
-> (Meta -> f Meta)
-> Pandoc
-> f Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Meta -> f Meta) -> Pandoc -> f Pandoc
forall a. HasMeta a => Lens' a Meta
Lens' Pandoc Meta
meta
class AsPandoc a where
_Pandoc ::
Prism' a Pandoc
instance AsPandoc Pandoc where
_Pandoc :: Prism' Pandoc Pandoc
_Pandoc =
p Pandoc (f Pandoc) -> p Pandoc (f Pandoc)
forall a. a -> a
id
instance AsPandoc D.Pandoc where
_Pandoc :: Prism' Pandoc Pandoc
_Pandoc =
AnIso Pandoc Pandoc Pandoc Pandoc
-> Iso Pandoc Pandoc Pandoc Pandoc
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Pandoc Pandoc Pandoc Pandoc
Iso' Pandoc Pandoc
isPandoc
isPandoc ::
Iso'
Pandoc
D.Pandoc
isPandoc :: Iso' Pandoc Pandoc
isPandoc =
(Pandoc -> Pandoc) -> (Pandoc -> Pandoc) -> Iso' Pandoc Pandoc
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Pandoc Meta
m [Block]
b) -> Meta -> [Block] -> Pandoc
D.Pandoc (Getting Meta Meta Meta -> Meta -> Meta
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Meta Meta Meta
Iso' Meta Meta
isMeta Meta
m) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b))
(\(D.Pandoc Meta
m [Block]
b) -> Meta -> [Block] -> Pandoc
Pandoc (AReview Meta Meta -> Meta -> Meta
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Meta Meta
Iso' Meta Meta
isMeta Meta
m) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b))
instance Walkable D.Pandoc Pandoc where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
walkM =
(Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
Iso' Pandoc Pandoc
isPandoc
query :: forall c. Monoid c => (Pandoc -> c) -> Pandoc -> c
query Pandoc -> c
f =
Pandoc -> c
f (Pandoc -> c) -> (Pandoc -> Pandoc) -> Pandoc -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Pandoc Pandoc Pandoc -> Pandoc -> Pandoc
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Pandoc Pandoc Pandoc
Iso' Pandoc Pandoc
isPandoc
instance Semigroup Pandoc where
Pandoc Meta
m1 [Block]
b1 <> :: Pandoc -> Pandoc -> Pandoc
<> Pandoc Meta
m2 [Block]
b2 =
Meta -> [Block] -> Pandoc
Pandoc (Meta
m1 Meta -> Meta -> Meta
forall a. Semigroup a => a -> a -> a
<> Meta
m2) ([Block]
b1 [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
b2)
instance Monoid Pandoc where
mempty :: Pandoc
mempty =
Meta -> [Block] -> Pandoc
Pandoc Meta
forall a. Monoid a => a
mempty [Block]
forall a. Monoid a => a
mempty
data Alignment =
AlignLeft
| AlignRight
| AlignCenter
| AlignDefault
deriving (Alignment -> Alignment -> Bool
(Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool) -> Eq Alignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Alignment -> Alignment -> Bool
== :: Alignment -> Alignment -> Bool
$c/= :: Alignment -> Alignment -> Bool
/= :: Alignment -> Alignment -> Bool
Eq, Eq Alignment
Eq Alignment =>
(Alignment -> Alignment -> Ordering)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Bool)
-> (Alignment -> Alignment -> Alignment)
-> (Alignment -> Alignment -> Alignment)
-> Ord Alignment
Alignment -> Alignment -> Bool
Alignment -> Alignment -> Ordering
Alignment -> Alignment -> Alignment
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 :: Alignment -> Alignment -> Ordering
compare :: Alignment -> Alignment -> Ordering
$c< :: Alignment -> Alignment -> Bool
< :: Alignment -> Alignment -> Bool
$c<= :: Alignment -> Alignment -> Bool
<= :: Alignment -> Alignment -> Bool
$c> :: Alignment -> Alignment -> Bool
> :: Alignment -> Alignment -> Bool
$c>= :: Alignment -> Alignment -> Bool
>= :: Alignment -> Alignment -> Bool
$cmax :: Alignment -> Alignment -> Alignment
max :: Alignment -> Alignment -> Alignment
$cmin :: Alignment -> Alignment -> Alignment
min :: Alignment -> Alignment -> Alignment
Ord, Int -> Alignment -> ShowS
[Alignment] -> ShowS
Alignment -> String
(Int -> Alignment -> ShowS)
-> (Alignment -> String)
-> ([Alignment] -> ShowS)
-> Show Alignment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Alignment -> ShowS
showsPrec :: Int -> Alignment -> ShowS
$cshow :: Alignment -> String
show :: Alignment -> String
$cshowList :: [Alignment] -> ShowS
showList :: [Alignment] -> ShowS
Show, Typeable Alignment
Typeable Alignment =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment)
-> (Alignment -> Constr)
-> (Alignment -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment))
-> ((forall b. Data b => b -> b) -> Alignment -> Alignment)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r)
-> (forall u. (forall d. Data d => d -> u) -> Alignment -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Alignment -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment)
-> Data Alignment
Alignment -> Constr
Alignment -> DataType
(forall b. Data b => b -> b) -> Alignment -> Alignment
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) -> Alignment -> u
forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Alignment -> c Alignment
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Alignment
$ctoConstr :: Alignment -> Constr
toConstr :: Alignment -> Constr
$cdataTypeOf :: Alignment -> DataType
dataTypeOf :: Alignment -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Alignment)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alignment)
$cgmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment
gmapT :: (forall b. Data b => b -> b) -> Alignment -> Alignment
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Alignment -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Alignment -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Alignment -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Alignment -> m Alignment
Data, Typeable, ReadPrec [Alignment]
ReadPrec Alignment
Int -> ReadS Alignment
ReadS [Alignment]
(Int -> ReadS Alignment)
-> ReadS [Alignment]
-> ReadPrec Alignment
-> ReadPrec [Alignment]
-> Read Alignment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Alignment
readsPrec :: Int -> ReadS Alignment
$creadList :: ReadS [Alignment]
readList :: ReadS [Alignment]
$creadPrec :: ReadPrec Alignment
readPrec :: ReadPrec Alignment
$creadListPrec :: ReadPrec [Alignment]
readListPrec :: ReadPrec [Alignment]
Read, (forall x. Alignment -> Rep Alignment x)
-> (forall x. Rep Alignment x -> Alignment) -> Generic Alignment
forall x. Rep Alignment x -> Alignment
forall x. Alignment -> Rep Alignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Alignment -> Rep Alignment x
from :: forall x. Alignment -> Rep Alignment x
$cto :: forall x. Rep Alignment x -> Alignment
to :: forall x. Rep Alignment x -> Alignment
Generic)
instance Semigroup Alignment where
Alignment
AlignLeft <> :: Alignment -> Alignment -> Alignment
<> Alignment
_ =
Alignment
AlignLeft
Alignment
AlignDefault <> Alignment
y =
Alignment
y
Alignment
AlignRight <> Alignment
_ =
Alignment
AlignRight
Alignment
AlignCenter <> Alignment
_ =
Alignment
AlignCenter
instance Monoid Alignment where
mempty :: Alignment
mempty =
Alignment
AlignDefault
class HasAlignment a where
alignment ::
Lens' a Alignment
instance HasAlignment Alignment where
alignment :: Lens' Alignment Alignment
alignment =
(Alignment -> f Alignment) -> Alignment -> f Alignment
forall a. a -> a
id
instance HasAlignment D.Alignment where
alignment :: Lens' Alignment Alignment
alignment =
AnIso Alignment Alignment Alignment Alignment
-> Iso Alignment Alignment Alignment Alignment
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Alignment Alignment Alignment Alignment
Iso' Alignment Alignment
isAlignment
class AsAlignment a where
_Alignment ::
Prism' a Alignment
_AlignLeft ::
Prism' a ()
_AlignLeft =
p Alignment (f Alignment) -> p a (f a)
forall a. AsAlignment a => Prism' a Alignment
Prism' a Alignment
_Alignment (p Alignment (f Alignment) -> p a (f a))
-> (p () (f ()) -> p Alignment (f Alignment))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Alignment (f Alignment)
forall a. AsAlignment a => Prism' a ()
Prism' Alignment ()
_AlignLeft
_AlignRight ::
Prism' a ()
_AlignRight =
p Alignment (f Alignment) -> p a (f a)
forall a. AsAlignment a => Prism' a Alignment
Prism' a Alignment
_Alignment (p Alignment (f Alignment) -> p a (f a))
-> (p () (f ()) -> p Alignment (f Alignment))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Alignment (f Alignment)
forall a. AsAlignment a => Prism' a ()
Prism' Alignment ()
_AlignRight
_AlignCenter ::
Prism' a ()
_AlignCenter =
p Alignment (f Alignment) -> p a (f a)
forall a. AsAlignment a => Prism' a Alignment
Prism' a Alignment
_Alignment (p Alignment (f Alignment) -> p a (f a))
-> (p () (f ()) -> p Alignment (f Alignment))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Alignment (f Alignment)
forall a. AsAlignment a => Prism' a ()
Prism' Alignment ()
_AlignCenter
_AlignDefault ::
Prism' a ()
_AlignDefault =
p Alignment (f Alignment) -> p a (f a)
forall a. AsAlignment a => Prism' a Alignment
Prism' a Alignment
_Alignment (p Alignment (f Alignment) -> p a (f a))
-> (p () (f ()) -> p Alignment (f Alignment))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Alignment (f Alignment)
forall a. AsAlignment a => Prism' a ()
Prism' Alignment ()
_AlignDefault
instance AsAlignment Alignment where
_Alignment :: Prism' Alignment Alignment
_Alignment =
p Alignment (f Alignment) -> p Alignment (f Alignment)
forall a. a -> a
id
_AlignLeft :: Prism' Alignment ()
_AlignLeft =
(() -> Alignment) -> (Alignment -> Maybe ()) -> Prism' Alignment ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Alignment
AlignLeft)
(\case
Alignment
AlignLeft -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Alignment
_ -> Maybe ()
forall a. Maybe a
Nothing
)
_AlignRight :: Prism' Alignment ()
_AlignRight =
(() -> Alignment) -> (Alignment -> Maybe ()) -> Prism' Alignment ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Alignment
AlignRight)
(\case
Alignment
AlignRight -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Alignment
_ -> Maybe ()
forall a. Maybe a
Nothing
)
_AlignCenter :: Prism' Alignment ()
_AlignCenter =
(() -> Alignment) -> (Alignment -> Maybe ()) -> Prism' Alignment ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Alignment
AlignCenter)
(\case
Alignment
AlignCenter -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Alignment
_ -> Maybe ()
forall a. Maybe a
Nothing
)
_AlignDefault :: Prism' Alignment ()
_AlignDefault =
(() -> Alignment) -> (Alignment -> Maybe ()) -> Prism' Alignment ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Alignment
AlignDefault)
(\case
Alignment
AlignDefault -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Alignment
_ -> Maybe ()
forall a. Maybe a
Nothing
)
instance AsAlignment D.Alignment where
_Alignment :: Prism' Alignment Alignment
_Alignment =
AnIso Alignment Alignment Alignment Alignment
-> Iso Alignment Alignment Alignment Alignment
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Alignment Alignment Alignment Alignment
Iso' Alignment Alignment
isAlignment
isAlignment ::
Iso'
Alignment
D.Alignment
isAlignment :: Iso' Alignment Alignment
isAlignment =
(Alignment -> Alignment)
-> (Alignment -> Alignment) -> Iso' Alignment Alignment
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
Alignment
AlignLeft -> Alignment
D.AlignLeft
Alignment
AlignRight -> Alignment
D.AlignRight
Alignment
AlignCenter -> Alignment
D.AlignCenter
Alignment
AlignDefault -> Alignment
D.AlignDefault
)
(\case
Alignment
D.AlignLeft -> Alignment
AlignLeft
Alignment
D.AlignRight -> Alignment
AlignRight
Alignment
D.AlignCenter -> Alignment
AlignCenter
Alignment
D.AlignDefault -> Alignment
AlignDefault
)
instance Walkable D.Alignment Alignment where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Alignment -> m Alignment) -> Alignment -> m Alignment
walkM =
(Alignment -> m Alignment) -> Alignment -> m Alignment
Iso' Alignment Alignment
isAlignment
query :: forall c. Monoid c => (Alignment -> c) -> Alignment -> c
query Alignment -> c
f =
Alignment -> c
f (Alignment -> c) -> (Alignment -> Alignment) -> Alignment -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Alignment Alignment Alignment -> Alignment -> Alignment
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Alignment Alignment Alignment
Iso' Alignment Alignment
isAlignment
data Attr =
Attr
Text
[Text]
[(Text, Text)]
deriving (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, 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, 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, Typeable, ReadPrec [Attr]
ReadPrec Attr
Int -> ReadS Attr
ReadS [Attr]
(Int -> ReadS Attr)
-> ReadS [Attr] -> ReadPrec Attr -> ReadPrec [Attr] -> Read Attr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Attr
readsPrec :: Int -> ReadS Attr
$creadList :: ReadS [Attr]
readList :: ReadS [Attr]
$creadPrec :: ReadPrec Attr
readPrec :: ReadPrec Attr
$creadListPrec :: ReadPrec [Attr]
readListPrec :: ReadPrec [Attr]
Read, (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 Text
s1 [Text]
s2 [(Text, Text)]
s3 <> :: Attr -> Attr -> Attr
<> Attr Text
t1 [Text]
t2 [(Text, Text)]
t3 =
Text -> [Text] -> [(Text, Text)] -> Attr
Attr (Text
s1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t1) ([Text]
s2 [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
t2) ([(Text, Text)]
s3 [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
t3)
instance Monoid Attr where
mempty :: Attr
mempty =
Text -> [Text] -> [(Text, Text)] -> Attr
Attr Text
forall a. Monoid a => a
mempty [Text]
forall a. Monoid a => a
mempty [(Text, Text)]
forall a. Monoid a => a
mempty
class HasAttr a where
attr ::
Lens' a Attr
identifier ::
Lens' a Text
identifier =
(Attr -> f Attr) -> a -> f a
forall a. HasAttr a => Lens' a Attr
Lens' a Attr
attr ((Attr -> f Attr) -> a -> f a)
-> ((Text -> f Text) -> Attr -> f Attr)
-> (Text -> f Text)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> f Text) -> Attr -> f Attr
forall a. HasAttr a => Lens' a Text
Lens' Attr Text
identifier
classes ::
Lens' a [Text]
classes =
(Attr -> f Attr) -> a -> f a
forall a. HasAttr a => Lens' a Attr
Lens' a Attr
attr ((Attr -> f Attr) -> a -> f a)
-> (([Text] -> f [Text]) -> Attr -> f Attr)
-> ([Text] -> f [Text])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> f [Text]) -> Attr -> f Attr
forall a. HasAttr a => Lens' a [Text]
Lens' Attr [Text]
classes
keyValuePairs ::
Lens' a [(Text, Text)]
keyValuePairs =
(Attr -> f Attr) -> a -> f a
forall a. HasAttr a => Lens' a Attr
Lens' a Attr
attr ((Attr -> f Attr) -> a -> f a)
-> (([(Text, Text)] -> f [(Text, Text)]) -> Attr -> f Attr)
-> ([(Text, Text)] -> f [(Text, Text)])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([(Text, Text)] -> f [(Text, Text)]) -> Attr -> f Attr
forall a. HasAttr a => Lens' a [(Text, Text)]
Lens' Attr [(Text, Text)]
keyValuePairs
instance HasAttr Attr where
attr :: Lens' Attr Attr
attr =
(Attr -> f Attr) -> Attr -> f Attr
forall a. a -> a
id
identifier :: Lens' Attr Text
identifier Text -> f Text
f (Attr Text
i [Text]
c [(Text, Text)]
kv) =
(Text -> Attr) -> f Text -> f Attr
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Text
i' -> Text -> [Text] -> [(Text, Text)] -> Attr
Attr Text
i' [Text]
c [(Text, Text)]
kv) (Text -> f Text
f Text
i)
classes :: Lens' Attr [Text]
classes [Text] -> f [Text]
f (Attr Text
i [Text]
c [(Text, Text)]
kv) =
([Text] -> Attr) -> f [Text] -> f Attr
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Text]
c' -> Text -> [Text] -> [(Text, Text)] -> Attr
Attr Text
i [Text]
c' [(Text, Text)]
kv) ([Text] -> f [Text]
f [Text]
c)
keyValuePairs :: Lens' Attr [(Text, Text)]
keyValuePairs [(Text, Text)] -> f [(Text, Text)]
f (Attr Text
i [Text]
c [(Text, Text)]
kv) =
([(Text, Text)] -> Attr) -> f [(Text, Text)] -> f Attr
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> [Text] -> [(Text, Text)] -> Attr
Attr Text
i [Text]
c) ([(Text, Text)] -> f [(Text, Text)]
f [(Text, Text)]
kv)
instance HasAttr D.Attr where
attr :: Lens' Attr Attr
attr =
AnIso Attr Attr Attr Attr -> Iso Attr Attr Attr Attr
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Attr Attr Attr Attr
Iso' Attr Attr
isAttr
class AsAttr a where
_Attr ::
Prism' a Attr
instance AsAttr Attr where
_Attr :: Prism' Attr Attr
_Attr =
p Attr (f Attr) -> p Attr (f Attr)
forall a. a -> a
id
instance AsAttr D.Attr where
_Attr :: Prism' Attr Attr
_Attr =
AnIso Attr Attr Attr Attr -> Iso Attr Attr Attr Attr
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Attr Attr Attr Attr
Iso' Attr Attr
isAttr
isAttr ::
Iso'
Attr
D.Attr
isAttr :: Iso' Attr Attr
isAttr =
(Attr -> Attr) -> (Attr -> Attr) -> Iso' Attr Attr
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Attr Text
i [Text]
c [(Text, Text)]
kv) -> (Text
i, [Text]
c, [(Text, Text)]
kv))
(\(Text
i, [Text]
c, [(Text, Text)]
kv) -> Text -> [Text] -> [(Text, Text)] -> Attr
Attr Text
i [Text]
c [(Text, Text)]
kv)
instance Walkable D.Attr Attr where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Attr -> m Attr) -> Attr -> m Attr
walkM =
(Attr -> m Attr) -> Attr -> m Attr
Iso' Attr Attr
isAttr
query :: forall c. Monoid c => (Attr -> c) -> Attr -> c
query Attr -> c
f =
Attr -> c
f (Attr -> c) -> (Attr -> Attr) -> Attr -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr
data Caption =
Caption
(Maybe ShortCaption)
[Block]
deriving (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, 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, 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, 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, Typeable, ReadPrec [Caption]
ReadPrec Caption
Int -> ReadS Caption
ReadS [Caption]
(Int -> ReadS Caption)
-> ReadS [Caption]
-> ReadPrec Caption
-> ReadPrec [Caption]
-> Read Caption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Caption
readsPrec :: Int -> ReadS Caption
$creadList :: ReadS [Caption]
readList :: ReadS [Caption]
$creadPrec :: ReadPrec Caption
readPrec :: ReadPrec Caption
$creadListPrec :: ReadPrec [Caption]
readListPrec :: ReadPrec [Caption]
Read, (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)
instance Semigroup Caption where
Caption Maybe ShortCaption
sc1 [Block]
b1 <> :: Caption -> Caption -> Caption
<> Caption Maybe ShortCaption
sc2 [Block]
b2 =
Maybe ShortCaption -> [Block] -> Caption
Caption (Maybe ShortCaption
sc1 Maybe ShortCaption -> Maybe ShortCaption -> Maybe ShortCaption
forall a. Semigroup a => a -> a -> a
<> Maybe ShortCaption
sc2) ([Block]
b1 [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
b2)
instance Monoid Caption where
mempty :: Caption
mempty =
Maybe ShortCaption -> [Block] -> Caption
Caption Maybe ShortCaption
forall a. Monoid a => a
mempty [Block]
forall a. Monoid a => a
mempty
class HasCaption a where
caption ::
Lens' a Caption
maybeShortCaption ::
Lens' a (Maybe ShortCaption)
maybeShortCaption =
(Caption -> f Caption) -> a -> f a
forall a. HasCaption a => Lens' a Caption
Lens' a Caption
caption ((Caption -> f Caption) -> a -> f a)
-> ((Maybe ShortCaption -> f (Maybe ShortCaption))
-> Caption -> f Caption)
-> (Maybe ShortCaption -> f (Maybe ShortCaption))
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe ShortCaption -> f (Maybe ShortCaption))
-> Caption -> f Caption
forall a. HasCaption a => Lens' a (Maybe ShortCaption)
Lens' Caption (Maybe ShortCaption)
maybeShortCaption
instance HasCaption Caption where
caption :: Lens' Caption Caption
caption =
(Caption -> f Caption) -> Caption -> f Caption
forall a. a -> a
id
maybeShortCaption :: Lens' Caption (Maybe ShortCaption)
maybeShortCaption Maybe ShortCaption -> f (Maybe ShortCaption)
f (Caption Maybe ShortCaption
s [Block]
b) =
(Maybe ShortCaption -> Caption)
-> f (Maybe ShortCaption) -> f Caption
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe ShortCaption -> [Block] -> Caption
`Caption` [Block]
b) (Maybe ShortCaption -> f (Maybe ShortCaption)
f Maybe ShortCaption
s)
instance HasBlocks Caption where
blocks :: Lens' Caption [Block]
blocks [Block] -> f [Block]
f (Caption Maybe ShortCaption
s [Block]
b) =
([Block] -> Caption) -> f [Block] -> f Caption
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Maybe ShortCaption -> [Block] -> Caption
Caption Maybe ShortCaption
s) ([Block] -> f [Block]
f [Block]
b)
instance HasCaption D.Caption where
caption :: Lens' Caption Caption
caption =
AnIso Caption Caption Caption Caption
-> Iso Caption Caption Caption Caption
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Caption Caption Caption Caption
Iso' Caption Caption
isCaption
class AsCaption a where
_Caption ::
Prism' a Caption
instance AsCaption Caption where
_Caption :: Prism' Caption Caption
_Caption =
p Caption (f Caption) -> p Caption (f Caption)
forall a. a -> a
id
instance AsCaption D.Caption where
_Caption :: Prism' Caption Caption
_Caption =
AnIso Caption Caption Caption Caption
-> Iso Caption Caption Caption Caption
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Caption Caption Caption Caption
Iso' Caption Caption
isCaption
isCaption ::
Iso'
Caption
D.Caption
isCaption :: Iso' Caption Caption
isCaption =
(Caption -> Caption)
-> (Caption -> Caption) -> Iso' Caption Caption
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Caption Maybe ShortCaption
c [Block]
b) -> Maybe ShortCaption -> [Block] -> Caption
D.Caption ((ShortCaption -> ShortCaption)
-> Maybe ShortCaption -> Maybe ShortCaption
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting ShortCaption ShortCaption ShortCaption
-> ShortCaption -> ShortCaption
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ShortCaption ShortCaption ShortCaption
Iso' ShortCaption ShortCaption
isShortCaption) Maybe ShortCaption
c) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b))
(\(D.Caption Maybe ShortCaption
c [Block]
b) -> Maybe ShortCaption -> [Block] -> Caption
Caption ((ShortCaption -> ShortCaption)
-> Maybe ShortCaption -> Maybe ShortCaption
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview ShortCaption ShortCaption -> ShortCaption -> ShortCaption
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ShortCaption ShortCaption
Iso' ShortCaption ShortCaption
isShortCaption) Maybe ShortCaption
c) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b))
instance Walkable D.Caption Caption where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Caption -> m Caption) -> Caption -> m Caption
walkM =
(Caption -> m Caption) -> Caption -> m Caption
Iso' Caption Caption
isCaption
query :: forall c. Monoid c => (Caption -> c) -> Caption -> c
query Caption -> c
f =
Caption -> c
f (Caption -> c) -> (Caption -> Caption) -> Caption -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Caption Caption Caption -> Caption -> Caption
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Caption Caption Caption
Iso' Caption Caption
isCaption
data CitationMode =
AuthorInText
| SuppressAuthor
| NormalCitation
deriving (CitationMode -> CitationMode -> Bool
(CitationMode -> CitationMode -> Bool)
-> (CitationMode -> CitationMode -> Bool) -> Eq CitationMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CitationMode -> CitationMode -> Bool
== :: CitationMode -> CitationMode -> Bool
$c/= :: CitationMode -> CitationMode -> Bool
/= :: CitationMode -> CitationMode -> Bool
Eq, Eq CitationMode
Eq CitationMode =>
(CitationMode -> CitationMode -> Ordering)
-> (CitationMode -> CitationMode -> Bool)
-> (CitationMode -> CitationMode -> Bool)
-> (CitationMode -> CitationMode -> Bool)
-> (CitationMode -> CitationMode -> Bool)
-> (CitationMode -> CitationMode -> CitationMode)
-> (CitationMode -> CitationMode -> CitationMode)
-> Ord CitationMode
CitationMode -> CitationMode -> Bool
CitationMode -> CitationMode -> Ordering
CitationMode -> CitationMode -> CitationMode
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 :: CitationMode -> CitationMode -> Ordering
compare :: CitationMode -> CitationMode -> Ordering
$c< :: CitationMode -> CitationMode -> Bool
< :: CitationMode -> CitationMode -> Bool
$c<= :: CitationMode -> CitationMode -> Bool
<= :: CitationMode -> CitationMode -> Bool
$c> :: CitationMode -> CitationMode -> Bool
> :: CitationMode -> CitationMode -> Bool
$c>= :: CitationMode -> CitationMode -> Bool
>= :: CitationMode -> CitationMode -> Bool
$cmax :: CitationMode -> CitationMode -> CitationMode
max :: CitationMode -> CitationMode -> CitationMode
$cmin :: CitationMode -> CitationMode -> CitationMode
min :: CitationMode -> CitationMode -> CitationMode
Ord, Int -> CitationMode -> ShowS
[CitationMode] -> ShowS
CitationMode -> String
(Int -> CitationMode -> ShowS)
-> (CitationMode -> String)
-> ([CitationMode] -> ShowS)
-> Show CitationMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CitationMode -> ShowS
showsPrec :: Int -> CitationMode -> ShowS
$cshow :: CitationMode -> String
show :: CitationMode -> String
$cshowList :: [CitationMode] -> ShowS
showList :: [CitationMode] -> ShowS
Show, Typeable CitationMode
Typeable CitationMode =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CitationMode -> c CitationMode)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CitationMode)
-> (CitationMode -> Constr)
-> (CitationMode -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CitationMode))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CitationMode))
-> ((forall b. Data b => b -> b) -> CitationMode -> CitationMode)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r)
-> (forall u. (forall d. Data d => d -> u) -> CitationMode -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CitationMode -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode)
-> Data CitationMode
CitationMode -> Constr
CitationMode -> DataType
(forall b. Data b => b -> b) -> CitationMode -> CitationMode
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) -> CitationMode -> u
forall u. (forall d. Data d => d -> u) -> CitationMode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CitationMode
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CitationMode -> c CitationMode
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CitationMode)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CitationMode)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CitationMode -> c CitationMode
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CitationMode -> c CitationMode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CitationMode
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CitationMode
$ctoConstr :: CitationMode -> Constr
toConstr :: CitationMode -> Constr
$cdataTypeOf :: CitationMode -> DataType
dataTypeOf :: CitationMode -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CitationMode)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CitationMode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CitationMode)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CitationMode)
$cgmapT :: (forall b. Data b => b -> b) -> CitationMode -> CitationMode
gmapT :: (forall b. Data b => b -> b) -> CitationMode -> CitationMode
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CitationMode -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CitationMode -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CitationMode -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CitationMode -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CitationMode -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CitationMode -> m CitationMode
Data, Typeable, ReadPrec [CitationMode]
ReadPrec CitationMode
Int -> ReadS CitationMode
ReadS [CitationMode]
(Int -> ReadS CitationMode)
-> ReadS [CitationMode]
-> ReadPrec CitationMode
-> ReadPrec [CitationMode]
-> Read CitationMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CitationMode
readsPrec :: Int -> ReadS CitationMode
$creadList :: ReadS [CitationMode]
readList :: ReadS [CitationMode]
$creadPrec :: ReadPrec CitationMode
readPrec :: ReadPrec CitationMode
$creadListPrec :: ReadPrec [CitationMode]
readListPrec :: ReadPrec [CitationMode]
Read, (forall x. CitationMode -> Rep CitationMode x)
-> (forall x. Rep CitationMode x -> CitationMode)
-> Generic CitationMode
forall x. Rep CitationMode x -> CitationMode
forall x. CitationMode -> Rep CitationMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CitationMode -> Rep CitationMode x
from :: forall x. CitationMode -> Rep CitationMode x
$cto :: forall x. Rep CitationMode x -> CitationMode
to :: forall x. Rep CitationMode x -> CitationMode
Generic)
class HasCitationMode a where
citationMode ::
Lens' a CitationMode
instance HasCitationMode CitationMode where
citationMode :: Lens' CitationMode CitationMode
citationMode =
(CitationMode -> f CitationMode) -> CitationMode -> f CitationMode
forall a. a -> a
id
instance HasCitationMode D.CitationMode where
citationMode :: Lens' CitationMode CitationMode
citationMode =
AnIso CitationMode CitationMode CitationMode CitationMode
-> Iso CitationMode CitationMode CitationMode CitationMode
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso CitationMode CitationMode CitationMode CitationMode
Iso' CitationMode CitationMode
isCitationMode
class AsCitationMode a where
_CitationMode ::
Prism' a CitationMode
_AuthorInText ::
Prism' a ()
_AuthorInText =
p CitationMode (f CitationMode) -> p a (f a)
forall a. AsCitationMode a => Prism' a CitationMode
Prism' a CitationMode
_CitationMode (p CitationMode (f CitationMode) -> p a (f a))
-> (p () (f ()) -> p CitationMode (f CitationMode))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p CitationMode (f CitationMode)
forall a. AsCitationMode a => Prism' a ()
Prism' CitationMode ()
_AuthorInText
_SuppressAuthor ::
Prism' a ()
_SuppressAuthor =
p CitationMode (f CitationMode) -> p a (f a)
forall a. AsCitationMode a => Prism' a CitationMode
Prism' a CitationMode
_CitationMode (p CitationMode (f CitationMode) -> p a (f a))
-> (p () (f ()) -> p CitationMode (f CitationMode))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p CitationMode (f CitationMode)
forall a. AsCitationMode a => Prism' a ()
Prism' CitationMode ()
_SuppressAuthor
_NormalCitation ::
Prism' a ()
_NormalCitation =
p CitationMode (f CitationMode) -> p a (f a)
forall a. AsCitationMode a => Prism' a CitationMode
Prism' a CitationMode
_CitationMode (p CitationMode (f CitationMode) -> p a (f a))
-> (p () (f ()) -> p CitationMode (f CitationMode))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p CitationMode (f CitationMode)
forall a. AsCitationMode a => Prism' a ()
Prism' CitationMode ()
_NormalCitation
instance AsCitationMode CitationMode where
_CitationMode :: Prism' CitationMode CitationMode
_CitationMode =
p CitationMode (f CitationMode) -> p CitationMode (f CitationMode)
forall a. a -> a
id
_AuthorInText :: Prism' CitationMode ()
_AuthorInText =
(() -> CitationMode)
-> (CitationMode -> Maybe ()) -> Prism' CitationMode ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> CitationMode
AuthorInText)
(\case
CitationMode
AuthorInText -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
CitationMode
_ -> Maybe ()
forall a. Maybe a
Nothing)
_SuppressAuthor :: Prism' CitationMode ()
_SuppressAuthor =
(() -> CitationMode)
-> (CitationMode -> Maybe ()) -> Prism' CitationMode ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> CitationMode
SuppressAuthor)
(\case
CitationMode
SuppressAuthor -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
CitationMode
_ -> Maybe ()
forall a. Maybe a
Nothing)
_NormalCitation :: Prism' CitationMode ()
_NormalCitation =
(() -> CitationMode)
-> (CitationMode -> Maybe ()) -> Prism' CitationMode ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> CitationMode
NormalCitation)
(\case
CitationMode
NormalCitation -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
CitationMode
_ -> Maybe ()
forall a. Maybe a
Nothing)
instance AsCitationMode D.CitationMode where
_CitationMode :: Prism' CitationMode CitationMode
_CitationMode =
AnIso CitationMode CitationMode CitationMode CitationMode
-> Iso CitationMode CitationMode CitationMode CitationMode
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso CitationMode CitationMode CitationMode CitationMode
Iso' CitationMode CitationMode
isCitationMode
isCitationMode ::
Iso'
CitationMode
D.CitationMode
isCitationMode :: Iso' CitationMode CitationMode
isCitationMode =
(CitationMode -> CitationMode)
-> (CitationMode -> CitationMode) -> Iso' CitationMode CitationMode
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
CitationMode
AuthorInText -> CitationMode
D.AuthorInText
CitationMode
SuppressAuthor -> CitationMode
D.SuppressAuthor
CitationMode
NormalCitation -> CitationMode
D.NormalCitation
)
(\case
CitationMode
D.AuthorInText -> CitationMode
AuthorInText
CitationMode
D.SuppressAuthor -> CitationMode
SuppressAuthor
CitationMode
D.NormalCitation -> CitationMode
NormalCitation
)
instance Walkable D.CitationMode CitationMode where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(CitationMode -> m CitationMode) -> CitationMode -> m CitationMode
walkM =
(CitationMode -> m CitationMode) -> CitationMode -> m CitationMode
Iso' CitationMode CitationMode
isCitationMode
query :: forall c. Monoid c => (CitationMode -> c) -> CitationMode -> c
query CitationMode -> c
f =
CitationMode -> c
f (CitationMode -> c)
-> (CitationMode -> CitationMode) -> CitationMode -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting CitationMode CitationMode CitationMode
-> CitationMode -> CitationMode
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting CitationMode CitationMode CitationMode
Iso' CitationMode CitationMode
isCitationMode
data ColSpec =
ColSpec
Alignment
ColWidth
deriving (ColSpec -> ColSpec -> Bool
(ColSpec -> ColSpec -> Bool)
-> (ColSpec -> ColSpec -> Bool) -> Eq ColSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColSpec -> ColSpec -> Bool
== :: ColSpec -> ColSpec -> Bool
$c/= :: ColSpec -> ColSpec -> Bool
/= :: ColSpec -> ColSpec -> Bool
Eq, Eq ColSpec
Eq ColSpec =>
(ColSpec -> ColSpec -> Ordering)
-> (ColSpec -> ColSpec -> Bool)
-> (ColSpec -> ColSpec -> Bool)
-> (ColSpec -> ColSpec -> Bool)
-> (ColSpec -> ColSpec -> Bool)
-> (ColSpec -> ColSpec -> ColSpec)
-> (ColSpec -> ColSpec -> ColSpec)
-> Ord ColSpec
ColSpec -> ColSpec -> Bool
ColSpec -> ColSpec -> Ordering
ColSpec -> ColSpec -> ColSpec
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 :: ColSpec -> ColSpec -> Ordering
compare :: ColSpec -> ColSpec -> Ordering
$c< :: ColSpec -> ColSpec -> Bool
< :: ColSpec -> ColSpec -> Bool
$c<= :: ColSpec -> ColSpec -> Bool
<= :: ColSpec -> ColSpec -> Bool
$c> :: ColSpec -> ColSpec -> Bool
> :: ColSpec -> ColSpec -> Bool
$c>= :: ColSpec -> ColSpec -> Bool
>= :: ColSpec -> ColSpec -> Bool
$cmax :: ColSpec -> ColSpec -> ColSpec
max :: ColSpec -> ColSpec -> ColSpec
$cmin :: ColSpec -> ColSpec -> ColSpec
min :: ColSpec -> ColSpec -> ColSpec
Ord, Int -> ColSpec -> ShowS
[ColSpec] -> ShowS
ColSpec -> String
(Int -> ColSpec -> ShowS)
-> (ColSpec -> String) -> ([ColSpec] -> ShowS) -> Show ColSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColSpec -> ShowS
showsPrec :: Int -> ColSpec -> ShowS
$cshow :: ColSpec -> String
show :: ColSpec -> String
$cshowList :: [ColSpec] -> ShowS
showList :: [ColSpec] -> ShowS
Show, Typeable ColSpec
Typeable ColSpec =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpec -> c ColSpec)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpec)
-> (ColSpec -> Constr)
-> (ColSpec -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpec))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpec))
-> ((forall b. Data b => b -> b) -> ColSpec -> ColSpec)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r)
-> (forall u. (forall d. Data d => d -> u) -> ColSpec -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ColSpec -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec)
-> Data ColSpec
ColSpec -> Constr
ColSpec -> DataType
(forall b. Data b => b -> b) -> ColSpec -> ColSpec
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) -> ColSpec -> u
forall u. (forall d. Data d => d -> u) -> ColSpec -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpec
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpec -> c ColSpec
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpec)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpec)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpec -> c ColSpec
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpec -> c ColSpec
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpec
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpec
$ctoConstr :: ColSpec -> Constr
toConstr :: ColSpec -> Constr
$cdataTypeOf :: ColSpec -> DataType
dataTypeOf :: ColSpec -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpec)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpec)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpec)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpec)
$cgmapT :: (forall b. Data b => b -> b) -> ColSpec -> ColSpec
gmapT :: (forall b. Data b => b -> b) -> ColSpec -> ColSpec
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpec -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColSpec -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ColSpec -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColSpec -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColSpec -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpec -> m ColSpec
Data, Typeable, ReadPrec [ColSpec]
ReadPrec ColSpec
Int -> ReadS ColSpec
ReadS [ColSpec]
(Int -> ReadS ColSpec)
-> ReadS [ColSpec]
-> ReadPrec ColSpec
-> ReadPrec [ColSpec]
-> Read ColSpec
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColSpec
readsPrec :: Int -> ReadS ColSpec
$creadList :: ReadS [ColSpec]
readList :: ReadS [ColSpec]
$creadPrec :: ReadPrec ColSpec
readPrec :: ReadPrec ColSpec
$creadListPrec :: ReadPrec [ColSpec]
readListPrec :: ReadPrec [ColSpec]
Read, (forall x. ColSpec -> Rep ColSpec x)
-> (forall x. Rep ColSpec x -> ColSpec) -> Generic ColSpec
forall x. Rep ColSpec x -> ColSpec
forall x. ColSpec -> Rep ColSpec x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColSpec -> Rep ColSpec x
from :: forall x. ColSpec -> Rep ColSpec x
$cto :: forall x. Rep ColSpec x -> ColSpec
to :: forall x. Rep ColSpec x -> ColSpec
Generic)
instance Semigroup ColSpec where
ColSpec Alignment
a1 ColWidth
w1 <> :: ColSpec -> ColSpec -> ColSpec
<> ColSpec Alignment
a2 ColWidth
w2 =
Alignment -> ColWidth -> ColSpec
ColSpec (Alignment
a1 Alignment -> Alignment -> Alignment
forall a. Semigroup a => a -> a -> a
<> Alignment
a2) (ColWidth
w1 ColWidth -> ColWidth -> ColWidth
forall a. Semigroup a => a -> a -> a
<> ColWidth
w2)
instance Monoid ColSpec where
mempty :: ColSpec
mempty =
Alignment -> ColWidth -> ColSpec
ColSpec Alignment
forall a. Monoid a => a
mempty ColWidth
forall a. Monoid a => a
mempty
class HasColSpec a where
colSpec ::
Lens' a ColSpec
instance HasColSpec ColSpec where
colSpec :: Lens' ColSpec ColSpec
colSpec =
(ColSpec -> f ColSpec) -> ColSpec -> f ColSpec
forall a. a -> a
id
instance HasAlignment ColSpec where
alignment :: Lens' ColSpec Alignment
alignment Alignment -> f Alignment
f (ColSpec Alignment
a ColWidth
w) =
(Alignment -> ColSpec) -> f Alignment -> f ColSpec
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Alignment -> ColWidth -> ColSpec
`ColSpec` ColWidth
w) (Alignment -> f Alignment
f Alignment
a)
instance HasColWidth ColSpec where
colWidth :: Lens' ColSpec ColWidth
colWidth ColWidth -> f ColWidth
f (ColSpec Alignment
a ColWidth
w) =
(ColWidth -> ColSpec) -> f ColWidth -> f ColSpec
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Alignment -> ColWidth -> ColSpec
ColSpec Alignment
a) (ColWidth -> f ColWidth
f ColWidth
w)
instance HasColSpec D.ColSpec where
colSpec :: Lens' ColSpec ColSpec
colSpec =
AnIso ColSpec ColSpec ColSpec ColSpec
-> Iso ColSpec ColSpec ColSpec ColSpec
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ColSpec ColSpec ColSpec ColSpec
Iso' ColSpec ColSpec
isColSpec
class AsColSpec a where
_ColSpec ::
Prism' a ColSpec
instance AsColSpec ColSpec where
_ColSpec :: Prism' ColSpec ColSpec
_ColSpec =
p ColSpec (f ColSpec) -> p ColSpec (f ColSpec)
forall a. a -> a
id
instance AsColSpec D.ColSpec where
_ColSpec :: Prism' ColSpec ColSpec
_ColSpec =
AnIso ColSpec ColSpec ColSpec ColSpec
-> Iso ColSpec ColSpec ColSpec ColSpec
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ColSpec ColSpec ColSpec ColSpec
Iso' ColSpec ColSpec
isColSpec
isColSpec ::
Iso'
ColSpec
D.ColSpec
isColSpec :: Iso' ColSpec ColSpec
isColSpec =
(ColSpec -> ColSpec)
-> (ColSpec -> ColSpec) -> Iso' ColSpec ColSpec
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(ColSpec Alignment
a ColWidth
w) -> (Getting Alignment Alignment Alignment -> Alignment -> Alignment
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Alignment Alignment Alignment
Iso' Alignment Alignment
isAlignment Alignment
a, Getting ColWidth ColWidth ColWidth -> ColWidth -> ColWidth
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ColWidth ColWidth ColWidth
Iso' ColWidth ColWidth
isColWidth ColWidth
w))
(\(Alignment
a, ColWidth
w) -> Alignment -> ColWidth -> ColSpec
ColSpec (AReview Alignment Alignment -> Alignment -> Alignment
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Alignment Alignment
Iso' Alignment Alignment
isAlignment Alignment
a) (AReview ColWidth ColWidth -> ColWidth -> ColWidth
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ColWidth ColWidth
Iso' ColWidth ColWidth
isColWidth ColWidth
w))
instance Walkable D.ColSpec ColSpec where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ColSpec -> m ColSpec) -> ColSpec -> m ColSpec
walkM =
(ColSpec -> m ColSpec) -> ColSpec -> m ColSpec
Iso' ColSpec ColSpec
isColSpec
query :: forall c. Monoid c => (ColSpec -> c) -> ColSpec -> c
query ColSpec -> c
f =
ColSpec -> c
f (ColSpec -> c) -> (ColSpec -> ColSpec) -> ColSpec -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ColSpec ColSpec ColSpec -> ColSpec -> ColSpec
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ColSpec ColSpec ColSpec
Iso' ColSpec ColSpec
isColSpec
data ColWidth =
ColWidth Double
| ColWidthDefault
deriving (ColWidth -> ColWidth -> Bool
(ColWidth -> ColWidth -> Bool)
-> (ColWidth -> ColWidth -> Bool) -> Eq ColWidth
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColWidth -> ColWidth -> Bool
== :: ColWidth -> ColWidth -> Bool
$c/= :: ColWidth -> ColWidth -> Bool
/= :: ColWidth -> ColWidth -> Bool
Eq, Eq ColWidth
Eq ColWidth =>
(ColWidth -> ColWidth -> Ordering)
-> (ColWidth -> ColWidth -> Bool)
-> (ColWidth -> ColWidth -> Bool)
-> (ColWidth -> ColWidth -> Bool)
-> (ColWidth -> ColWidth -> Bool)
-> (ColWidth -> ColWidth -> ColWidth)
-> (ColWidth -> ColWidth -> ColWidth)
-> Ord ColWidth
ColWidth -> ColWidth -> Bool
ColWidth -> ColWidth -> Ordering
ColWidth -> ColWidth -> ColWidth
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 :: ColWidth -> ColWidth -> Ordering
compare :: ColWidth -> ColWidth -> Ordering
$c< :: ColWidth -> ColWidth -> Bool
< :: ColWidth -> ColWidth -> Bool
$c<= :: ColWidth -> ColWidth -> Bool
<= :: ColWidth -> ColWidth -> Bool
$c> :: ColWidth -> ColWidth -> Bool
> :: ColWidth -> ColWidth -> Bool
$c>= :: ColWidth -> ColWidth -> Bool
>= :: ColWidth -> ColWidth -> Bool
$cmax :: ColWidth -> ColWidth -> ColWidth
max :: ColWidth -> ColWidth -> ColWidth
$cmin :: ColWidth -> ColWidth -> ColWidth
min :: ColWidth -> ColWidth -> ColWidth
Ord, Int -> ColWidth -> ShowS
[ColWidth] -> ShowS
ColWidth -> String
(Int -> ColWidth -> ShowS)
-> (ColWidth -> String) -> ([ColWidth] -> ShowS) -> Show ColWidth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColWidth -> ShowS
showsPrec :: Int -> ColWidth -> ShowS
$cshow :: ColWidth -> String
show :: ColWidth -> String
$cshowList :: [ColWidth] -> ShowS
showList :: [ColWidth] -> ShowS
Show, Typeable ColWidth
Typeable ColWidth =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColWidth -> c ColWidth)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColWidth)
-> (ColWidth -> Constr)
-> (ColWidth -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColWidth))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth))
-> ((forall b. Data b => b -> b) -> ColWidth -> ColWidth)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r)
-> (forall u. (forall d. Data d => d -> u) -> ColWidth -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ColWidth -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth)
-> Data ColWidth
ColWidth -> Constr
ColWidth -> DataType
(forall b. Data b => b -> b) -> ColWidth -> ColWidth
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) -> ColWidth -> u
forall u. (forall d. Data d => d -> u) -> ColWidth -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColWidth
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColWidth -> c ColWidth
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColWidth)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColWidth -> c ColWidth
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColWidth -> c ColWidth
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColWidth
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColWidth
$ctoConstr :: ColWidth -> Constr
toConstr :: ColWidth -> Constr
$cdataTypeOf :: ColWidth -> DataType
dataTypeOf :: ColWidth -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColWidth)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColWidth)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColWidth)
$cgmapT :: (forall b. Data b => b -> b) -> ColWidth -> ColWidth
gmapT :: (forall b. Data b => b -> b) -> ColWidth -> ColWidth
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColWidth -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColWidth -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ColWidth -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColWidth -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColWidth -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColWidth -> m ColWidth
Data, Typeable, ReadPrec [ColWidth]
ReadPrec ColWidth
Int -> ReadS ColWidth
ReadS [ColWidth]
(Int -> ReadS ColWidth)
-> ReadS [ColWidth]
-> ReadPrec ColWidth
-> ReadPrec [ColWidth]
-> Read ColWidth
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColWidth
readsPrec :: Int -> ReadS ColWidth
$creadList :: ReadS [ColWidth]
readList :: ReadS [ColWidth]
$creadPrec :: ReadPrec ColWidth
readPrec :: ReadPrec ColWidth
$creadListPrec :: ReadPrec [ColWidth]
readListPrec :: ReadPrec [ColWidth]
Read, (forall x. ColWidth -> Rep ColWidth x)
-> (forall x. Rep ColWidth x -> ColWidth) -> Generic ColWidth
forall x. Rep ColWidth x -> ColWidth
forall x. ColWidth -> Rep ColWidth x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColWidth -> Rep ColWidth x
from :: forall x. ColWidth -> Rep ColWidth x
$cto :: forall x. Rep ColWidth x -> ColWidth
to :: forall x. Rep ColWidth x -> ColWidth
Generic)
instance Semigroup ColWidth where
ColWidth
ColWidthDefault <> :: ColWidth -> ColWidth -> ColWidth
<> ColWidth
y =
ColWidth
y
ColWidth Double
x <> ColWidth
_ =
Double -> ColWidth
ColWidth Double
x
instance Monoid ColWidth where
mempty :: ColWidth
mempty =
ColWidth
ColWidthDefault
class HasColWidth a where
colWidth ::
Lens' a ColWidth
instance HasColWidth ColWidth where
colWidth :: Lens' ColWidth ColWidth
colWidth =
(ColWidth -> f ColWidth) -> ColWidth -> f ColWidth
forall a. a -> a
id
instance HasColWidth D.ColWidth where
colWidth :: Lens' ColWidth ColWidth
colWidth =
AnIso ColWidth ColWidth ColWidth ColWidth
-> Iso ColWidth ColWidth ColWidth ColWidth
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ColWidth ColWidth ColWidth ColWidth
Iso' ColWidth ColWidth
isColWidth
class AsColWidth a where
_ColWidth ::
Prism' a ColWidth
_ColWidth' ::
Prism' a Double
_ColWidth' =
p ColWidth (f ColWidth) -> p a (f a)
forall a. AsColWidth a => Prism' a ColWidth
Prism' a ColWidth
_ColWidth (p ColWidth (f ColWidth) -> p a (f a))
-> (p Double (f Double) -> p ColWidth (f ColWidth))
-> p Double (f Double)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Double (f Double) -> p ColWidth (f ColWidth)
forall a. AsColWidth a => Prism' a Double
Prism' ColWidth Double
_ColWidth'
_ColWidthDefault ::
Prism' a ()
_ColWidthDefault =
p ColWidth (f ColWidth) -> p a (f a)
forall a. AsColWidth a => Prism' a ColWidth
Prism' a ColWidth
_ColWidth (p ColWidth (f ColWidth) -> p a (f a))
-> (p () (f ()) -> p ColWidth (f ColWidth))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ColWidth (f ColWidth)
forall a. AsColWidth a => Prism' a ()
Prism' ColWidth ()
_ColWidthDefault
instance AsColWidth ColWidth where
_ColWidth :: Prism' ColWidth ColWidth
_ColWidth =
p ColWidth (f ColWidth) -> p ColWidth (f ColWidth)
forall a. a -> a
id
instance AsColWidth D.ColWidth where
_ColWidth :: Prism' ColWidth ColWidth
_ColWidth =
AnIso ColWidth ColWidth ColWidth ColWidth
-> Iso ColWidth ColWidth ColWidth ColWidth
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ColWidth ColWidth ColWidth ColWidth
Iso' ColWidth ColWidth
isColWidth
isColWidth ::
Iso'
ColWidth
D.ColWidth
isColWidth :: Iso' ColWidth ColWidth
isColWidth =
(ColWidth -> ColWidth)
-> (ColWidth -> ColWidth) -> Iso' ColWidth ColWidth
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
ColWidth Double
d -> Double -> ColWidth
D.ColWidth Double
d
ColWidth
ColWidthDefault -> ColWidth
D.ColWidthDefault
)
(\case
D.ColWidth Double
d -> Double -> ColWidth
ColWidth Double
d
ColWidth
D.ColWidthDefault -> ColWidth
ColWidthDefault
)
instance Walkable D.ColWidth ColWidth where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ColWidth -> m ColWidth) -> ColWidth -> m ColWidth
walkM =
(ColWidth -> m ColWidth) -> ColWidth -> m ColWidth
Iso' ColWidth ColWidth
isColWidth
query :: forall c. Monoid c => (ColWidth -> c) -> ColWidth -> c
query ColWidth -> c
f =
ColWidth -> c
f (ColWidth -> c) -> (ColWidth -> ColWidth) -> ColWidth -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ColWidth ColWidth ColWidth -> ColWidth -> ColWidth
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ColWidth ColWidth ColWidth
Iso' ColWidth ColWidth
isColWidth
newtype Format =
Format D.Format
deriving (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, 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, 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, Typeable, ReadPrec [Format]
ReadPrec Format
Int -> ReadS Format
ReadS [Format]
(Int -> ReadS Format)
-> ReadS [Format]
-> ReadPrec Format
-> ReadPrec [Format]
-> Read Format
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Format
readsPrec :: Int -> ReadS Format
$creadList :: ReadS [Format]
readList :: ReadS [Format]
$creadPrec :: ReadPrec Format
readPrec :: ReadPrec Format
$creadListPrec :: ReadPrec [Format]
readListPrec :: ReadPrec [Format]
Read, (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)
instance (Format ~ t) => Rewrapped Format t
instance Wrapped Format where
type Unwrapped Format =
D.Format
_Wrapped' :: Iso' Format (Unwrapped Format)
_Wrapped' =
(Format -> Format)
-> (Format -> Format) -> Iso Format Format Format Format
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(Format Format
x) -> Format
x) Format -> Format
Format
class HasFormat a where
format ::
Lens' a Format
instance HasFormat Format where
format :: Lens' Format Format
format =
(Format -> f Format) -> Format -> f Format
forall a. a -> a
id
instance HasFormat D.Format where
format :: Lens' Format Format
format =
AnIso Format Format Format Format
-> Iso Format Format Format Format
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Format Format Format Format
Iso Format Format Format Format
isFormat
class AsFormat a where
_Format ::
Prism' a Format
instance AsFormat Format where
_Format :: Prism' Format Format
_Format =
p Format (f Format) -> p Format (f Format)
forall a. a -> a
id
instance AsFormat D.Format where
_Format :: Prism' Format Format
_Format =
AnIso Format Format Format Format
-> Iso Format Format Format Format
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Format Format Format Format
Iso Format Format Format Format
isFormat
isFormat ::
Iso'
Format
D.Format
isFormat :: Iso Format Format Format Format
isFormat =
(Format -> Format)
-> (Format -> Format) -> Iso Format Format Format Format
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Format Format
x) -> Format
x)
Format -> Format
Format
instance Walkable D.Format Format where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Format -> m Format) -> Format -> m Format
walkM =
(Format -> m Format) -> Format -> m Format
Iso Format Format Format Format
isFormat
query :: forall c. Monoid c => (Format -> c) -> Format -> c
query Format -> c
f =
Format -> c
f (Format -> c) -> (Format -> Format) -> Format -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Format Format Format -> Format -> Format
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Format Format Format
Iso Format Format Format Format
isFormat
data ListAttributes =
ListAttributes
Int
ListNumberStyle
ListNumberDelim
deriving (ListAttributes -> ListAttributes -> Bool
(ListAttributes -> ListAttributes -> Bool)
-> (ListAttributes -> ListAttributes -> Bool) -> Eq ListAttributes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListAttributes -> ListAttributes -> Bool
== :: ListAttributes -> ListAttributes -> Bool
$c/= :: ListAttributes -> ListAttributes -> Bool
/= :: ListAttributes -> ListAttributes -> Bool
Eq, Eq ListAttributes
Eq ListAttributes =>
(ListAttributes -> ListAttributes -> Ordering)
-> (ListAttributes -> ListAttributes -> Bool)
-> (ListAttributes -> ListAttributes -> Bool)
-> (ListAttributes -> ListAttributes -> Bool)
-> (ListAttributes -> ListAttributes -> Bool)
-> (ListAttributes -> ListAttributes -> ListAttributes)
-> (ListAttributes -> ListAttributes -> ListAttributes)
-> Ord ListAttributes
ListAttributes -> ListAttributes -> Bool
ListAttributes -> ListAttributes -> Ordering
ListAttributes -> ListAttributes -> ListAttributes
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 :: ListAttributes -> ListAttributes -> Ordering
compare :: ListAttributes -> ListAttributes -> Ordering
$c< :: ListAttributes -> ListAttributes -> Bool
< :: ListAttributes -> ListAttributes -> Bool
$c<= :: ListAttributes -> ListAttributes -> Bool
<= :: ListAttributes -> ListAttributes -> Bool
$c> :: ListAttributes -> ListAttributes -> Bool
> :: ListAttributes -> ListAttributes -> Bool
$c>= :: ListAttributes -> ListAttributes -> Bool
>= :: ListAttributes -> ListAttributes -> Bool
$cmax :: ListAttributes -> ListAttributes -> ListAttributes
max :: ListAttributes -> ListAttributes -> ListAttributes
$cmin :: ListAttributes -> ListAttributes -> ListAttributes
min :: ListAttributes -> ListAttributes -> ListAttributes
Ord, Int -> ListAttributes -> ShowS
[ListAttributes] -> ShowS
ListAttributes -> String
(Int -> ListAttributes -> ShowS)
-> (ListAttributes -> String)
-> ([ListAttributes] -> ShowS)
-> Show ListAttributes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListAttributes -> ShowS
showsPrec :: Int -> ListAttributes -> ShowS
$cshow :: ListAttributes -> String
show :: ListAttributes -> String
$cshowList :: [ListAttributes] -> ShowS
showList :: [ListAttributes] -> ShowS
Show, Typeable ListAttributes
Typeable ListAttributes =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListAttributes -> c ListAttributes)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListAttributes)
-> (ListAttributes -> Constr)
-> (ListAttributes -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListAttributes))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListAttributes))
-> ((forall b. Data b => b -> b)
-> ListAttributes -> ListAttributes)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ListAttributes -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ListAttributes -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes)
-> Data ListAttributes
ListAttributes -> Constr
ListAttributes -> DataType
(forall b. Data b => b -> b) -> ListAttributes -> ListAttributes
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) -> ListAttributes -> u
forall u. (forall d. Data d => d -> u) -> ListAttributes -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListAttributes
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListAttributes -> c ListAttributes
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListAttributes)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListAttributes)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListAttributes -> c ListAttributes
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListAttributes -> c ListAttributes
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListAttributes
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListAttributes
$ctoConstr :: ListAttributes -> Constr
toConstr :: ListAttributes -> Constr
$cdataTypeOf :: ListAttributes -> DataType
dataTypeOf :: ListAttributes -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListAttributes)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListAttributes)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListAttributes)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListAttributes)
$cgmapT :: (forall b. Data b => b -> b) -> ListAttributes -> ListAttributes
gmapT :: (forall b. Data b => b -> b) -> ListAttributes -> ListAttributes
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListAttributes -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListAttributes -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ListAttributes -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ListAttributes -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ListAttributes -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListAttributes -> m ListAttributes
Data, Typeable, ReadPrec [ListAttributes]
ReadPrec ListAttributes
Int -> ReadS ListAttributes
ReadS [ListAttributes]
(Int -> ReadS ListAttributes)
-> ReadS [ListAttributes]
-> ReadPrec ListAttributes
-> ReadPrec [ListAttributes]
-> Read ListAttributes
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListAttributes
readsPrec :: Int -> ReadS ListAttributes
$creadList :: ReadS [ListAttributes]
readList :: ReadS [ListAttributes]
$creadPrec :: ReadPrec ListAttributes
readPrec :: ReadPrec ListAttributes
$creadListPrec :: ReadPrec [ListAttributes]
readListPrec :: ReadPrec [ListAttributes]
Read, (forall x. ListAttributes -> Rep ListAttributes x)
-> (forall x. Rep ListAttributes x -> ListAttributes)
-> Generic ListAttributes
forall x. Rep ListAttributes x -> ListAttributes
forall x. ListAttributes -> Rep ListAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListAttributes -> Rep ListAttributes x
from :: forall x. ListAttributes -> Rep ListAttributes x
$cto :: forall x. Rep ListAttributes x -> ListAttributes
to :: forall x. Rep ListAttributes x -> ListAttributes
Generic)
instance Semigroup ListAttributes where
ListAttributes Int
n1 ListNumberStyle
s1 ListNumberDelim
d1 <> :: ListAttributes -> ListAttributes -> ListAttributes
<> ListAttributes Int
n2 ListNumberStyle
s2 ListNumberDelim
d2 =
Int -> ListNumberStyle -> ListNumberDelim -> ListAttributes
ListAttributes (Int
n1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n2) (ListNumberStyle
s1 ListNumberStyle -> ListNumberStyle -> ListNumberStyle
forall a. Semigroup a => a -> a -> a
<> ListNumberStyle
s2) (ListNumberDelim
d1 ListNumberDelim -> ListNumberDelim -> ListNumberDelim
forall a. Semigroup a => a -> a -> a
<> ListNumberDelim
d2)
instance Monoid ListAttributes where
mempty :: ListAttributes
mempty =
Int -> ListNumberStyle -> ListNumberDelim -> ListAttributes
ListAttributes Int
0 ListNumberStyle
forall a. Monoid a => a
mempty ListNumberDelim
forall a. Monoid a => a
mempty
class HasListAttributes a where
listAttributes ::
Lens' a ListAttributes
listAttributesStart ::
Lens' a Int
listAttributesStart =
(ListAttributes -> f ListAttributes) -> a -> f a
forall a. HasListAttributes a => Lens' a ListAttributes
Lens' a ListAttributes
listAttributes ((ListAttributes -> f ListAttributes) -> a -> f a)
-> ((Int -> f Int) -> ListAttributes -> f ListAttributes)
-> (Int -> f Int)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> f Int) -> ListAttributes -> f ListAttributes
forall a. HasListAttributes a => Lens' a Int
Lens' ListAttributes Int
listAttributesStart
instance HasListAttributes ListAttributes where
listAttributes :: Lens' ListAttributes ListAttributes
listAttributes =
(ListAttributes -> f ListAttributes)
-> ListAttributes -> f ListAttributes
forall a. a -> a
id
listAttributesStart :: Lens' ListAttributes Int
listAttributesStart Int -> f Int
f (ListAttributes Int
n ListNumberStyle
s ListNumberDelim
d) =
(Int -> ListAttributes) -> f Int -> f ListAttributes
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
n' -> Int -> ListNumberStyle -> ListNumberDelim -> ListAttributes
ListAttributes Int
n' ListNumberStyle
s ListNumberDelim
d) (Int -> f Int
f Int
n)
instance HasListNumberStyle ListAttributes where
listNumberStyle :: Lens' ListAttributes ListNumberStyle
listNumberStyle ListNumberStyle -> f ListNumberStyle
f (ListAttributes Int
n ListNumberStyle
s ListNumberDelim
d) =
(ListNumberStyle -> ListAttributes)
-> f ListNumberStyle -> f ListAttributes
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ListNumberStyle
s' -> Int -> ListNumberStyle -> ListNumberDelim -> ListAttributes
ListAttributes Int
n ListNumberStyle
s' ListNumberDelim
d) (ListNumberStyle -> f ListNumberStyle
f ListNumberStyle
s)
instance HasListNumberDelim ListAttributes where
listNumberDelim :: Lens' ListAttributes ListNumberDelim
listNumberDelim ListNumberDelim -> f ListNumberDelim
f (ListAttributes Int
n ListNumberStyle
s ListNumberDelim
d) =
(ListNumberDelim -> ListAttributes)
-> f ListNumberDelim -> f ListAttributes
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> ListNumberStyle -> ListNumberDelim -> ListAttributes
ListAttributes Int
n ListNumberStyle
s) (ListNumberDelim -> f ListNumberDelim
f ListNumberDelim
d)
instance HasListAttributes D.ListAttributes where
listAttributes :: Lens' ListAttributes ListAttributes
listAttributes =
AnIso ListAttributes ListAttributes ListAttributes ListAttributes
-> Iso ListAttributes ListAttributes ListAttributes ListAttributes
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ListAttributes ListAttributes ListAttributes ListAttributes
Iso' ListAttributes ListAttributes
isListAttributes
class AsListAttributes a where
_ListAttributes ::
Prism' a ListAttributes
instance AsListAttributes ListAttributes where
_ListAttributes :: Prism' ListAttributes ListAttributes
_ListAttributes =
p ListAttributes (f ListAttributes)
-> p ListAttributes (f ListAttributes)
forall a. a -> a
id
instance AsListAttributes D.ListAttributes where
_ListAttributes :: Prism' ListAttributes ListAttributes
_ListAttributes =
AnIso ListAttributes ListAttributes ListAttributes ListAttributes
-> Iso ListAttributes ListAttributes ListAttributes ListAttributes
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ListAttributes ListAttributes ListAttributes ListAttributes
Iso' ListAttributes ListAttributes
isListAttributes
isListAttributes ::
Iso'
ListAttributes
D.ListAttributes
isListAttributes :: Iso' ListAttributes ListAttributes
isListAttributes =
(ListAttributes -> ListAttributes)
-> (ListAttributes -> ListAttributes)
-> Iso' ListAttributes ListAttributes
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(ListAttributes Int
n ListNumberStyle
s ListNumberDelim
d) -> (Int
n, Getting ListNumberStyle ListNumberStyle ListNumberStyle
-> ListNumberStyle -> ListNumberStyle
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListNumberStyle ListNumberStyle ListNumberStyle
Iso' ListNumberStyle ListNumberStyle
isListNumberStyle ListNumberStyle
s, Getting ListNumberDelim ListNumberDelim ListNumberDelim
-> ListNumberDelim -> ListNumberDelim
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListNumberDelim ListNumberDelim ListNumberDelim
Iso' ListNumberDelim ListNumberDelim
isListNumberDelim ListNumberDelim
d))
(\(Int
n, ListNumberStyle
s, ListNumberDelim
d) -> Int -> ListNumberStyle -> ListNumberDelim -> ListAttributes
ListAttributes Int
n (AReview ListNumberStyle ListNumberStyle
-> ListNumberStyle -> ListNumberStyle
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ListNumberStyle ListNumberStyle
Iso' ListNumberStyle ListNumberStyle
isListNumberStyle ListNumberStyle
s) (AReview ListNumberDelim ListNumberDelim
-> ListNumberDelim -> ListNumberDelim
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ListNumberDelim ListNumberDelim
Iso' ListNumberDelim ListNumberDelim
isListNumberDelim ListNumberDelim
d))
instance Walkable D.ListAttributes ListAttributes where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ListAttributes -> m ListAttributes)
-> ListAttributes -> m ListAttributes
walkM =
(ListAttributes -> m ListAttributes)
-> ListAttributes -> m ListAttributes
Iso' ListAttributes ListAttributes
isListAttributes
query :: forall c. Monoid c => (ListAttributes -> c) -> ListAttributes -> c
query ListAttributes -> c
f =
ListAttributes -> c
f (ListAttributes -> c)
-> (ListAttributes -> ListAttributes) -> ListAttributes -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ListAttributes ListAttributes ListAttributes
-> ListAttributes -> ListAttributes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListAttributes ListAttributes ListAttributes
Iso' ListAttributes ListAttributes
isListAttributes
data ListNumberDelim =
DefaultDelim
| Period
| OneParen
| TwoParens
deriving (ListNumberDelim -> ListNumberDelim -> Bool
(ListNumberDelim -> ListNumberDelim -> Bool)
-> (ListNumberDelim -> ListNumberDelim -> Bool)
-> Eq ListNumberDelim
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListNumberDelim -> ListNumberDelim -> Bool
== :: ListNumberDelim -> ListNumberDelim -> Bool
$c/= :: ListNumberDelim -> ListNumberDelim -> Bool
/= :: ListNumberDelim -> ListNumberDelim -> Bool
Eq, Eq ListNumberDelim
Eq ListNumberDelim =>
(ListNumberDelim -> ListNumberDelim -> Ordering)
-> (ListNumberDelim -> ListNumberDelim -> Bool)
-> (ListNumberDelim -> ListNumberDelim -> Bool)
-> (ListNumberDelim -> ListNumberDelim -> Bool)
-> (ListNumberDelim -> ListNumberDelim -> Bool)
-> (ListNumberDelim -> ListNumberDelim -> ListNumberDelim)
-> (ListNumberDelim -> ListNumberDelim -> ListNumberDelim)
-> Ord ListNumberDelim
ListNumberDelim -> ListNumberDelim -> Bool
ListNumberDelim -> ListNumberDelim -> Ordering
ListNumberDelim -> ListNumberDelim -> ListNumberDelim
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 :: ListNumberDelim -> ListNumberDelim -> Ordering
compare :: ListNumberDelim -> ListNumberDelim -> Ordering
$c< :: ListNumberDelim -> ListNumberDelim -> Bool
< :: ListNumberDelim -> ListNumberDelim -> Bool
$c<= :: ListNumberDelim -> ListNumberDelim -> Bool
<= :: ListNumberDelim -> ListNumberDelim -> Bool
$c> :: ListNumberDelim -> ListNumberDelim -> Bool
> :: ListNumberDelim -> ListNumberDelim -> Bool
$c>= :: ListNumberDelim -> ListNumberDelim -> Bool
>= :: ListNumberDelim -> ListNumberDelim -> Bool
$cmax :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim
max :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim
$cmin :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim
min :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim
Ord, Int -> ListNumberDelim -> ShowS
[ListNumberDelim] -> ShowS
ListNumberDelim -> String
(Int -> ListNumberDelim -> ShowS)
-> (ListNumberDelim -> String)
-> ([ListNumberDelim] -> ShowS)
-> Show ListNumberDelim
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListNumberDelim -> ShowS
showsPrec :: Int -> ListNumberDelim -> ShowS
$cshow :: ListNumberDelim -> String
show :: ListNumberDelim -> String
$cshowList :: [ListNumberDelim] -> ShowS
showList :: [ListNumberDelim] -> ShowS
Show, Typeable ListNumberDelim
Typeable ListNumberDelim =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberDelim)
-> (ListNumberDelim -> Constr)
-> (ListNumberDelim -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberDelim))
-> ((forall b. Data b => b -> b)
-> ListNumberDelim -> ListNumberDelim)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ListNumberDelim -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ListNumberDelim -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim)
-> Data ListNumberDelim
ListNumberDelim -> Constr
ListNumberDelim -> DataType
(forall b. Data b => b -> b) -> ListNumberDelim -> ListNumberDelim
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) -> ListNumberDelim -> u
forall u. (forall d. Data d => d -> u) -> ListNumberDelim -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberDelim
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberDelim)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberDelim -> c ListNumberDelim
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberDelim
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberDelim
$ctoConstr :: ListNumberDelim -> Constr
toConstr :: ListNumberDelim -> Constr
$cdataTypeOf :: ListNumberDelim -> DataType
dataTypeOf :: ListNumberDelim -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberDelim)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberDelim)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberDelim)
$cgmapT :: (forall b. Data b => b -> b) -> ListNumberDelim -> ListNumberDelim
gmapT :: (forall b. Data b => b -> b) -> ListNumberDelim -> ListNumberDelim
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberDelim -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberDelim -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberDelim -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ListNumberDelim -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ListNumberDelim -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberDelim -> m ListNumberDelim
Data, Typeable, ReadPrec [ListNumberDelim]
ReadPrec ListNumberDelim
Int -> ReadS ListNumberDelim
ReadS [ListNumberDelim]
(Int -> ReadS ListNumberDelim)
-> ReadS [ListNumberDelim]
-> ReadPrec ListNumberDelim
-> ReadPrec [ListNumberDelim]
-> Read ListNumberDelim
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListNumberDelim
readsPrec :: Int -> ReadS ListNumberDelim
$creadList :: ReadS [ListNumberDelim]
readList :: ReadS [ListNumberDelim]
$creadPrec :: ReadPrec ListNumberDelim
readPrec :: ReadPrec ListNumberDelim
$creadListPrec :: ReadPrec [ListNumberDelim]
readListPrec :: ReadPrec [ListNumberDelim]
Read, (forall x. ListNumberDelim -> Rep ListNumberDelim x)
-> (forall x. Rep ListNumberDelim x -> ListNumberDelim)
-> Generic ListNumberDelim
forall x. Rep ListNumberDelim x -> ListNumberDelim
forall x. ListNumberDelim -> Rep ListNumberDelim x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListNumberDelim -> Rep ListNumberDelim x
from :: forall x. ListNumberDelim -> Rep ListNumberDelim x
$cto :: forall x. Rep ListNumberDelim x -> ListNumberDelim
to :: forall x. Rep ListNumberDelim x -> ListNumberDelim
Generic)
instance Semigroup ListNumberDelim where
ListNumberDelim
DefaultDelim <> :: ListNumberDelim -> ListNumberDelim -> ListNumberDelim
<> ListNumberDelim
y =
ListNumberDelim
y
ListNumberDelim
Period <> ListNumberDelim
_ =
ListNumberDelim
Period
ListNumberDelim
OneParen <> ListNumberDelim
_ =
ListNumberDelim
OneParen
ListNumberDelim
TwoParens <> ListNumberDelim
_ =
ListNumberDelim
TwoParens
instance Monoid ListNumberDelim where
mempty :: ListNumberDelim
mempty =
ListNumberDelim
DefaultDelim
class HasListNumberDelim a where
listNumberDelim ::
Lens' a ListNumberDelim
instance HasListNumberDelim ListNumberDelim where
listNumberDelim :: Lens' ListNumberDelim ListNumberDelim
listNumberDelim =
(ListNumberDelim -> f ListNumberDelim)
-> ListNumberDelim -> f ListNumberDelim
forall a. a -> a
id
instance HasListNumberDelim D.ListNumberDelim where
listNumberDelim :: Lens' ListNumberDelim ListNumberDelim
listNumberDelim =
AnIso
ListNumberDelim ListNumberDelim ListNumberDelim ListNumberDelim
-> Iso
ListNumberDelim ListNumberDelim ListNumberDelim ListNumberDelim
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso
ListNumberDelim ListNumberDelim ListNumberDelim ListNumberDelim
Iso' ListNumberDelim ListNumberDelim
isListNumberDelim
class AsListNumberDelim a where
_ListNumberDelim ::
Prism' a ListNumberDelim
_DefaultDelim ::
Prism' a ()
_DefaultDelim =
p ListNumberDelim (f ListNumberDelim) -> p a (f a)
forall a. AsListNumberDelim a => Prism' a ListNumberDelim
Prism' a ListNumberDelim
_ListNumberDelim (p ListNumberDelim (f ListNumberDelim) -> p a (f a))
-> (p () (f ()) -> p ListNumberDelim (f ListNumberDelim))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberDelim (f ListNumberDelim)
forall a. AsListNumberDelim a => Prism' a ()
Prism' ListNumberDelim ()
_DefaultDelim
_Period ::
Prism' a ()
_Period =
p ListNumberDelim (f ListNumberDelim) -> p a (f a)
forall a. AsListNumberDelim a => Prism' a ListNumberDelim
Prism' a ListNumberDelim
_ListNumberDelim (p ListNumberDelim (f ListNumberDelim) -> p a (f a))
-> (p () (f ()) -> p ListNumberDelim (f ListNumberDelim))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberDelim (f ListNumberDelim)
forall a. AsListNumberDelim a => Prism' a ()
Prism' ListNumberDelim ()
_Period
_OneParen ::
Prism' a ()
_OneParen =
p ListNumberDelim (f ListNumberDelim) -> p a (f a)
forall a. AsListNumberDelim a => Prism' a ListNumberDelim
Prism' a ListNumberDelim
_ListNumberDelim (p ListNumberDelim (f ListNumberDelim) -> p a (f a))
-> (p () (f ()) -> p ListNumberDelim (f ListNumberDelim))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberDelim (f ListNumberDelim)
forall a. AsListNumberDelim a => Prism' a ()
Prism' ListNumberDelim ()
_OneParen
_TwoParens ::
Prism' a ()
_TwoParens =
p ListNumberDelim (f ListNumberDelim) -> p a (f a)
forall a. AsListNumberDelim a => Prism' a ListNumberDelim
Prism' a ListNumberDelim
_ListNumberDelim (p ListNumberDelim (f ListNumberDelim) -> p a (f a))
-> (p () (f ()) -> p ListNumberDelim (f ListNumberDelim))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberDelim (f ListNumberDelim)
forall a. AsListNumberDelim a => Prism' a ()
Prism' ListNumberDelim ()
_TwoParens
instance AsListNumberDelim ListNumberDelim where
_ListNumberDelim :: Prism' ListNumberDelim ListNumberDelim
_ListNumberDelim =
p ListNumberDelim (f ListNumberDelim)
-> p ListNumberDelim (f ListNumberDelim)
forall a. a -> a
id
_DefaultDelim :: Prism' ListNumberDelim ()
_DefaultDelim =
(() -> ListNumberDelim)
-> (ListNumberDelim -> Maybe ()) -> Prism' ListNumberDelim ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> ListNumberDelim
DefaultDelim)
(\case
ListNumberDelim
DefaultDelim -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
ListNumberDelim
_ -> Maybe ()
forall a. Maybe a
Nothing)
_Period :: Prism' ListNumberDelim ()
_Period =
(() -> ListNumberDelim)
-> (ListNumberDelim -> Maybe ()) -> Prism' ListNumberDelim ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> ListNumberDelim
Period)
(\case
ListNumberDelim
Period -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
ListNumberDelim
_ -> Maybe ()
forall a. Maybe a
Nothing)
_OneParen :: Prism' ListNumberDelim ()
_OneParen =
(() -> ListNumberDelim)
-> (ListNumberDelim -> Maybe ()) -> Prism' ListNumberDelim ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> ListNumberDelim
OneParen)
(\case
ListNumberDelim
OneParen -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
ListNumberDelim
_ -> Maybe ()
forall a. Maybe a
Nothing)
_TwoParens :: Prism' ListNumberDelim ()
_TwoParens =
(() -> ListNumberDelim)
-> (ListNumberDelim -> Maybe ()) -> Prism' ListNumberDelim ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> ListNumberDelim
TwoParens)
(\case
ListNumberDelim
TwoParens -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
ListNumberDelim
_ -> Maybe ()
forall a. Maybe a
Nothing)
instance AsListNumberDelim D.ListNumberDelim where
_ListNumberDelim :: Prism' ListNumberDelim ListNumberDelim
_ListNumberDelim =
AnIso
ListNumberDelim ListNumberDelim ListNumberDelim ListNumberDelim
-> Iso
ListNumberDelim ListNumberDelim ListNumberDelim ListNumberDelim
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso
ListNumberDelim ListNumberDelim ListNumberDelim ListNumberDelim
Iso' ListNumberDelim ListNumberDelim
isListNumberDelim
isListNumberDelim ::
Iso'
ListNumberDelim
D.ListNumberDelim
isListNumberDelim :: Iso' ListNumberDelim ListNumberDelim
isListNumberDelim =
(ListNumberDelim -> ListNumberDelim)
-> (ListNumberDelim -> ListNumberDelim)
-> Iso' ListNumberDelim ListNumberDelim
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
ListNumberDelim
DefaultDelim -> ListNumberDelim
D.DefaultDelim
ListNumberDelim
Period -> ListNumberDelim
D.Period
ListNumberDelim
OneParen -> ListNumberDelim
D.OneParen
ListNumberDelim
TwoParens -> ListNumberDelim
D.TwoParens
)
(\case
ListNumberDelim
D.DefaultDelim -> ListNumberDelim
DefaultDelim
ListNumberDelim
D.Period -> ListNumberDelim
Period
ListNumberDelim
D.OneParen -> ListNumberDelim
OneParen
ListNumberDelim
D.TwoParens -> ListNumberDelim
TwoParens
)
instance Walkable D.ListNumberDelim ListNumberDelim where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ListNumberDelim -> m ListNumberDelim)
-> ListNumberDelim -> m ListNumberDelim
walkM =
(ListNumberDelim -> m ListNumberDelim)
-> ListNumberDelim -> m ListNumberDelim
Iso' ListNumberDelim ListNumberDelim
isListNumberDelim
query :: forall c.
Monoid c =>
(ListNumberDelim -> c) -> ListNumberDelim -> c
query ListNumberDelim -> c
f =
ListNumberDelim -> c
f (ListNumberDelim -> c)
-> (ListNumberDelim -> ListNumberDelim) -> ListNumberDelim -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ListNumberDelim ListNumberDelim ListNumberDelim
-> ListNumberDelim -> ListNumberDelim
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListNumberDelim ListNumberDelim ListNumberDelim
Iso' ListNumberDelim ListNumberDelim
isListNumberDelim
data ListNumberStyle =
DefaultStyle
| Example
| Decimal
| LowerRoman
| UpperRoman
| LowerAlpha
| UpperAlpha
deriving (ListNumberStyle -> ListNumberStyle -> Bool
(ListNumberStyle -> ListNumberStyle -> Bool)
-> (ListNumberStyle -> ListNumberStyle -> Bool)
-> Eq ListNumberStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListNumberStyle -> ListNumberStyle -> Bool
== :: ListNumberStyle -> ListNumberStyle -> Bool
$c/= :: ListNumberStyle -> ListNumberStyle -> Bool
/= :: ListNumberStyle -> ListNumberStyle -> Bool
Eq, Eq ListNumberStyle
Eq ListNumberStyle =>
(ListNumberStyle -> ListNumberStyle -> Ordering)
-> (ListNumberStyle -> ListNumberStyle -> Bool)
-> (ListNumberStyle -> ListNumberStyle -> Bool)
-> (ListNumberStyle -> ListNumberStyle -> Bool)
-> (ListNumberStyle -> ListNumberStyle -> Bool)
-> (ListNumberStyle -> ListNumberStyle -> ListNumberStyle)
-> (ListNumberStyle -> ListNumberStyle -> ListNumberStyle)
-> Ord ListNumberStyle
ListNumberStyle -> ListNumberStyle -> Bool
ListNumberStyle -> ListNumberStyle -> Ordering
ListNumberStyle -> ListNumberStyle -> ListNumberStyle
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 :: ListNumberStyle -> ListNumberStyle -> Ordering
compare :: ListNumberStyle -> ListNumberStyle -> Ordering
$c< :: ListNumberStyle -> ListNumberStyle -> Bool
< :: ListNumberStyle -> ListNumberStyle -> Bool
$c<= :: ListNumberStyle -> ListNumberStyle -> Bool
<= :: ListNumberStyle -> ListNumberStyle -> Bool
$c> :: ListNumberStyle -> ListNumberStyle -> Bool
> :: ListNumberStyle -> ListNumberStyle -> Bool
$c>= :: ListNumberStyle -> ListNumberStyle -> Bool
>= :: ListNumberStyle -> ListNumberStyle -> Bool
$cmax :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle
max :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle
$cmin :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle
min :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle
Ord, Int -> ListNumberStyle -> ShowS
[ListNumberStyle] -> ShowS
ListNumberStyle -> String
(Int -> ListNumberStyle -> ShowS)
-> (ListNumberStyle -> String)
-> ([ListNumberStyle] -> ShowS)
-> Show ListNumberStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListNumberStyle -> ShowS
showsPrec :: Int -> ListNumberStyle -> ShowS
$cshow :: ListNumberStyle -> String
show :: ListNumberStyle -> String
$cshowList :: [ListNumberStyle] -> ShowS
showList :: [ListNumberStyle] -> ShowS
Show, Typeable ListNumberStyle
Typeable ListNumberStyle =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberStyle)
-> (ListNumberStyle -> Constr)
-> (ListNumberStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberStyle))
-> ((forall b. Data b => b -> b)
-> ListNumberStyle -> ListNumberStyle)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ListNumberStyle -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ListNumberStyle -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle)
-> Data ListNumberStyle
ListNumberStyle -> Constr
ListNumberStyle -> DataType
(forall b. Data b => b -> b) -> ListNumberStyle -> ListNumberStyle
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) -> ListNumberStyle -> u
forall u. (forall d. Data d => d -> u) -> ListNumberStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberStyle)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListNumberStyle -> c ListNumberStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberStyle
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListNumberStyle
$ctoConstr :: ListNumberStyle -> Constr
toConstr :: ListNumberStyle -> Constr
$cdataTypeOf :: ListNumberStyle -> DataType
dataTypeOf :: ListNumberStyle -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListNumberStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberStyle)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ListNumberStyle)
$cgmapT :: (forall b. Data b => b -> b) -> ListNumberStyle -> ListNumberStyle
gmapT :: (forall b. Data b => b -> b) -> ListNumberStyle -> ListNumberStyle
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListNumberStyle -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberStyle -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ListNumberStyle -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ListNumberStyle -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ListNumberStyle -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ListNumberStyle -> m ListNumberStyle
Data, Typeable, ReadPrec [ListNumberStyle]
ReadPrec ListNumberStyle
Int -> ReadS ListNumberStyle
ReadS [ListNumberStyle]
(Int -> ReadS ListNumberStyle)
-> ReadS [ListNumberStyle]
-> ReadPrec ListNumberStyle
-> ReadPrec [ListNumberStyle]
-> Read ListNumberStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListNumberStyle
readsPrec :: Int -> ReadS ListNumberStyle
$creadList :: ReadS [ListNumberStyle]
readList :: ReadS [ListNumberStyle]
$creadPrec :: ReadPrec ListNumberStyle
readPrec :: ReadPrec ListNumberStyle
$creadListPrec :: ReadPrec [ListNumberStyle]
readListPrec :: ReadPrec [ListNumberStyle]
Read, (forall x. ListNumberStyle -> Rep ListNumberStyle x)
-> (forall x. Rep ListNumberStyle x -> ListNumberStyle)
-> Generic ListNumberStyle
forall x. Rep ListNumberStyle x -> ListNumberStyle
forall x. ListNumberStyle -> Rep ListNumberStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListNumberStyle -> Rep ListNumberStyle x
from :: forall x. ListNumberStyle -> Rep ListNumberStyle x
$cto :: forall x. Rep ListNumberStyle x -> ListNumberStyle
to :: forall x. Rep ListNumberStyle x -> ListNumberStyle
Generic)
instance Semigroup ListNumberStyle where
ListNumberStyle
DefaultStyle <> :: ListNumberStyle -> ListNumberStyle -> ListNumberStyle
<> ListNumberStyle
y =
ListNumberStyle
y
ListNumberStyle
Example <> ListNumberStyle
_ =
ListNumberStyle
Example
ListNumberStyle
Decimal <> ListNumberStyle
_ =
ListNumberStyle
Decimal
ListNumberStyle
LowerRoman <> ListNumberStyle
_ =
ListNumberStyle
LowerRoman
ListNumberStyle
UpperRoman <> ListNumberStyle
_ =
ListNumberStyle
UpperRoman
ListNumberStyle
LowerAlpha <> ListNumberStyle
_ =
ListNumberStyle
LowerAlpha
ListNumberStyle
UpperAlpha <> ListNumberStyle
_ =
ListNumberStyle
UpperAlpha
instance Monoid ListNumberStyle where
mempty :: ListNumberStyle
mempty =
ListNumberStyle
DefaultStyle
class HasListNumberStyle a where
listNumberStyle ::
Lens' a ListNumberStyle
instance HasListNumberStyle ListNumberStyle where
listNumberStyle :: Lens' ListNumberStyle ListNumberStyle
listNumberStyle =
(ListNumberStyle -> f ListNumberStyle)
-> ListNumberStyle -> f ListNumberStyle
forall a. a -> a
id
instance HasListNumberStyle D.ListNumberStyle where
listNumberStyle :: Lens' ListNumberStyle ListNumberStyle
listNumberStyle =
AnIso
ListNumberStyle ListNumberStyle ListNumberStyle ListNumberStyle
-> Iso
ListNumberStyle ListNumberStyle ListNumberStyle ListNumberStyle
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso
ListNumberStyle ListNumberStyle ListNumberStyle ListNumberStyle
Iso' ListNumberStyle ListNumberStyle
isListNumberStyle
class AsListNumberStyle a where
_ListNumberStyle ::
Prism' a ListNumberStyle
_DefaultStyle ::
Prism' a ()
_DefaultStyle =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_DefaultStyle
_Example ::
Prism' a ()
_Example =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_Example
_Decimal ::
Prism' a ()
_Decimal =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_Decimal
_LowerRoman ::
Prism' a ()
_LowerRoman =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_LowerRoman
_UpperRoman ::
Prism' a ()
_UpperRoman =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_UpperRoman
_LowerAlpha ::
Prism' a ()
_LowerAlpha =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_LowerAlpha
_UpperAlpha ::
Prism' a ()
_UpperAlpha =
p ListNumberStyle (f ListNumberStyle) -> p a (f a)
forall a. AsListNumberStyle a => Prism' a ListNumberStyle
Prism' a ListNumberStyle
_ListNumberStyle (p ListNumberStyle (f ListNumberStyle) -> p a (f a))
-> (p () (f ()) -> p ListNumberStyle (f ListNumberStyle))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p ListNumberStyle (f ListNumberStyle)
forall a. AsListNumberStyle a => Prism' a ()
Prism' ListNumberStyle ()
_UpperAlpha
instance AsListNumberStyle ListNumberStyle where
_ListNumberStyle :: Prism' ListNumberStyle ListNumberStyle
_ListNumberStyle =
p ListNumberStyle (f ListNumberStyle)
-> p ListNumberStyle (f ListNumberStyle)
forall a. a -> a
id
instance AsListNumberStyle D.ListNumberStyle where
_ListNumberStyle :: Prism' ListNumberStyle ListNumberStyle
_ListNumberStyle =
AnIso
ListNumberStyle ListNumberStyle ListNumberStyle ListNumberStyle
-> Iso
ListNumberStyle ListNumberStyle ListNumberStyle ListNumberStyle
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso
ListNumberStyle ListNumberStyle ListNumberStyle ListNumberStyle
Iso' ListNumberStyle ListNumberStyle
isListNumberStyle
isListNumberStyle ::
Iso'
ListNumberStyle
D.ListNumberStyle
isListNumberStyle :: Iso' ListNumberStyle ListNumberStyle
isListNumberStyle =
(ListNumberStyle -> ListNumberStyle)
-> (ListNumberStyle -> ListNumberStyle)
-> Iso' ListNumberStyle ListNumberStyle
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
ListNumberStyle
DefaultStyle -> ListNumberStyle
D.DefaultStyle
ListNumberStyle
Example -> ListNumberStyle
D.Example
ListNumberStyle
Decimal -> ListNumberStyle
D.Decimal
ListNumberStyle
LowerRoman -> ListNumberStyle
D.LowerRoman
ListNumberStyle
UpperRoman -> ListNumberStyle
D.UpperRoman
ListNumberStyle
LowerAlpha -> ListNumberStyle
D.LowerAlpha
ListNumberStyle
UpperAlpha -> ListNumberStyle
D.UpperAlpha
)
(\case
ListNumberStyle
D.DefaultStyle -> ListNumberStyle
DefaultStyle
ListNumberStyle
D.Example -> ListNumberStyle
Example
ListNumberStyle
D.Decimal -> ListNumberStyle
Decimal
ListNumberStyle
D.LowerRoman -> ListNumberStyle
LowerRoman
ListNumberStyle
D.UpperRoman -> ListNumberStyle
UpperRoman
ListNumberStyle
D.LowerAlpha -> ListNumberStyle
LowerAlpha
ListNumberStyle
D.UpperAlpha -> ListNumberStyle
UpperAlpha
)
instance Walkable D.ListNumberStyle ListNumberStyle where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ListNumberStyle -> m ListNumberStyle)
-> ListNumberStyle -> m ListNumberStyle
walkM =
(ListNumberStyle -> m ListNumberStyle)
-> ListNumberStyle -> m ListNumberStyle
Iso' ListNumberStyle ListNumberStyle
isListNumberStyle
query :: forall c.
Monoid c =>
(ListNumberStyle -> c) -> ListNumberStyle -> c
query ListNumberStyle -> c
f =
ListNumberStyle -> c
f (ListNumberStyle -> c)
-> (ListNumberStyle -> ListNumberStyle) -> ListNumberStyle -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ListNumberStyle ListNumberStyle ListNumberStyle
-> ListNumberStyle -> ListNumberStyle
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListNumberStyle ListNumberStyle ListNumberStyle
Iso' ListNumberStyle ListNumberStyle
isListNumberStyle
newtype RowSpan =
RowSpan D.RowSpan
deriving (RowSpan -> RowSpan -> Bool
(RowSpan -> RowSpan -> Bool)
-> (RowSpan -> RowSpan -> Bool) -> Eq RowSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RowSpan -> RowSpan -> Bool
== :: RowSpan -> RowSpan -> Bool
$c/= :: RowSpan -> RowSpan -> Bool
/= :: RowSpan -> RowSpan -> Bool
Eq, Eq RowSpan
Eq RowSpan =>
(RowSpan -> RowSpan -> Ordering)
-> (RowSpan -> RowSpan -> Bool)
-> (RowSpan -> RowSpan -> Bool)
-> (RowSpan -> RowSpan -> Bool)
-> (RowSpan -> RowSpan -> Bool)
-> (RowSpan -> RowSpan -> RowSpan)
-> (RowSpan -> RowSpan -> RowSpan)
-> Ord RowSpan
RowSpan -> RowSpan -> Bool
RowSpan -> RowSpan -> Ordering
RowSpan -> RowSpan -> RowSpan
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 :: RowSpan -> RowSpan -> Ordering
compare :: RowSpan -> RowSpan -> Ordering
$c< :: RowSpan -> RowSpan -> Bool
< :: RowSpan -> RowSpan -> Bool
$c<= :: RowSpan -> RowSpan -> Bool
<= :: RowSpan -> RowSpan -> Bool
$c> :: RowSpan -> RowSpan -> Bool
> :: RowSpan -> RowSpan -> Bool
$c>= :: RowSpan -> RowSpan -> Bool
>= :: RowSpan -> RowSpan -> Bool
$cmax :: RowSpan -> RowSpan -> RowSpan
max :: RowSpan -> RowSpan -> RowSpan
$cmin :: RowSpan -> RowSpan -> RowSpan
min :: RowSpan -> RowSpan -> RowSpan
Ord, Int -> RowSpan -> ShowS
[RowSpan] -> ShowS
RowSpan -> String
(Int -> RowSpan -> ShowS)
-> (RowSpan -> String) -> ([RowSpan] -> ShowS) -> Show RowSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RowSpan -> ShowS
showsPrec :: Int -> RowSpan -> ShowS
$cshow :: RowSpan -> String
show :: RowSpan -> String
$cshowList :: [RowSpan] -> ShowS
showList :: [RowSpan] -> ShowS
Show, Typeable RowSpan
Typeable RowSpan =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowSpan -> c RowSpan)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowSpan)
-> (RowSpan -> Constr)
-> (RowSpan -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowSpan))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan))
-> ((forall b. Data b => b -> b) -> RowSpan -> RowSpan)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r)
-> (forall u. (forall d. Data d => d -> u) -> RowSpan -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> RowSpan -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan)
-> Data RowSpan
RowSpan -> Constr
RowSpan -> DataType
(forall b. Data b => b -> b) -> RowSpan -> RowSpan
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) -> RowSpan -> u
forall u. (forall d. Data d => d -> u) -> RowSpan -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowSpan
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowSpan -> c RowSpan
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowSpan)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowSpan -> c RowSpan
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowSpan -> c RowSpan
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowSpan
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowSpan
$ctoConstr :: RowSpan -> Constr
toConstr :: RowSpan -> Constr
$cdataTypeOf :: RowSpan -> DataType
dataTypeOf :: RowSpan -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowSpan)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowSpan)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowSpan)
$cgmapT :: (forall b. Data b => b -> b) -> RowSpan -> RowSpan
gmapT :: (forall b. Data b => b -> b) -> RowSpan -> RowSpan
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowSpan -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RowSpan -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RowSpan -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowSpan -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowSpan -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowSpan -> m RowSpan
Data, Typeable, ReadPrec [RowSpan]
ReadPrec RowSpan
Int -> ReadS RowSpan
ReadS [RowSpan]
(Int -> ReadS RowSpan)
-> ReadS [RowSpan]
-> ReadPrec RowSpan
-> ReadPrec [RowSpan]
-> Read RowSpan
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RowSpan
readsPrec :: Int -> ReadS RowSpan
$creadList :: ReadS [RowSpan]
readList :: ReadS [RowSpan]
$creadPrec :: ReadPrec RowSpan
readPrec :: ReadPrec RowSpan
$creadListPrec :: ReadPrec [RowSpan]
readListPrec :: ReadPrec [RowSpan]
Read, (forall x. RowSpan -> Rep RowSpan x)
-> (forall x. Rep RowSpan x -> RowSpan) -> Generic RowSpan
forall x. Rep RowSpan x -> RowSpan
forall x. RowSpan -> Rep RowSpan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RowSpan -> Rep RowSpan x
from :: forall x. RowSpan -> Rep RowSpan x
$cto :: forall x. Rep RowSpan x -> RowSpan
to :: forall x. Rep RowSpan x -> RowSpan
Generic, Integer -> RowSpan
RowSpan -> RowSpan
RowSpan -> RowSpan -> RowSpan
(RowSpan -> RowSpan -> RowSpan)
-> (RowSpan -> RowSpan -> RowSpan)
-> (RowSpan -> RowSpan -> RowSpan)
-> (RowSpan -> RowSpan)
-> (RowSpan -> RowSpan)
-> (RowSpan -> RowSpan)
-> (Integer -> RowSpan)
-> Num RowSpan
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: RowSpan -> RowSpan -> RowSpan
+ :: RowSpan -> RowSpan -> RowSpan
$c- :: RowSpan -> RowSpan -> RowSpan
- :: RowSpan -> RowSpan -> RowSpan
$c* :: RowSpan -> RowSpan -> RowSpan
* :: RowSpan -> RowSpan -> RowSpan
$cnegate :: RowSpan -> RowSpan
negate :: RowSpan -> RowSpan
$cabs :: RowSpan -> RowSpan
abs :: RowSpan -> RowSpan
$csignum :: RowSpan -> RowSpan
signum :: RowSpan -> RowSpan
$cfromInteger :: Integer -> RowSpan
fromInteger :: Integer -> RowSpan
Num)
instance Semigroup RowSpan where
RowSpan
x <> :: RowSpan -> RowSpan -> RowSpan
<> RowSpan
y =
RowSpan
x RowSpan -> RowSpan -> RowSpan
forall a. Num a => a -> a -> a
+ RowSpan
y
instance Monoid RowSpan where
mempty :: RowSpan
mempty =
RowSpan
0
instance (RowSpan ~ t) => Rewrapped RowSpan t
instance Wrapped RowSpan where
type Unwrapped RowSpan =
D.RowSpan
_Wrapped' :: Iso' RowSpan (Unwrapped RowSpan)
_Wrapped' =
(RowSpan -> RowSpan)
-> (RowSpan -> RowSpan) -> Iso RowSpan RowSpan RowSpan RowSpan
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(RowSpan RowSpan
x) -> RowSpan
x) RowSpan -> RowSpan
RowSpan
class HasRowSpan a where
rowSpan ::
Lens' a RowSpan
instance HasRowSpan RowSpan where
rowSpan :: Lens' RowSpan RowSpan
rowSpan =
(RowSpan -> f RowSpan) -> RowSpan -> f RowSpan
forall a. a -> a
id
instance HasRowSpan D.RowSpan where
rowSpan :: Lens' RowSpan RowSpan
rowSpan =
AnIso RowSpan RowSpan RowSpan RowSpan
-> Iso RowSpan RowSpan RowSpan RowSpan
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso RowSpan RowSpan RowSpan RowSpan
Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan
class AsRowSpan a where
_RowSpan ::
Prism' a RowSpan
instance AsRowSpan RowSpan where
_RowSpan :: Prism' RowSpan RowSpan
_RowSpan =
p RowSpan (f RowSpan) -> p RowSpan (f RowSpan)
forall a. a -> a
id
instance AsRowSpan D.RowSpan where
_RowSpan :: Prism' RowSpan RowSpan
_RowSpan =
AnIso RowSpan RowSpan RowSpan RowSpan
-> Iso RowSpan RowSpan RowSpan RowSpan
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso RowSpan RowSpan RowSpan RowSpan
Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan
isRowSpan ::
Iso'
RowSpan
D.RowSpan
isRowSpan :: Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan =
(RowSpan -> RowSpan)
-> (RowSpan -> RowSpan) -> Iso RowSpan RowSpan RowSpan RowSpan
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(RowSpan RowSpan
x) -> RowSpan
x)
RowSpan -> RowSpan
RowSpan
instance Walkable D.RowSpan RowSpan where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(RowSpan -> m RowSpan) -> RowSpan -> m RowSpan
walkM =
(RowSpan -> m RowSpan) -> RowSpan -> m RowSpan
Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan
query :: forall c. Monoid c => (RowSpan -> c) -> RowSpan -> c
query RowSpan -> c
f =
RowSpan -> c
f (RowSpan -> c) -> (RowSpan -> RowSpan) -> RowSpan -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting RowSpan RowSpan RowSpan -> RowSpan -> RowSpan
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting RowSpan RowSpan RowSpan
Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan
newtype ColSpan =
ColSpan D.ColSpan
deriving (ColSpan -> ColSpan -> Bool
(ColSpan -> ColSpan -> Bool)
-> (ColSpan -> ColSpan -> Bool) -> Eq ColSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColSpan -> ColSpan -> Bool
== :: ColSpan -> ColSpan -> Bool
$c/= :: ColSpan -> ColSpan -> Bool
/= :: ColSpan -> ColSpan -> Bool
Eq, Eq ColSpan
Eq ColSpan =>
(ColSpan -> ColSpan -> Ordering)
-> (ColSpan -> ColSpan -> Bool)
-> (ColSpan -> ColSpan -> Bool)
-> (ColSpan -> ColSpan -> Bool)
-> (ColSpan -> ColSpan -> Bool)
-> (ColSpan -> ColSpan -> ColSpan)
-> (ColSpan -> ColSpan -> ColSpan)
-> Ord ColSpan
ColSpan -> ColSpan -> Bool
ColSpan -> ColSpan -> Ordering
ColSpan -> ColSpan -> ColSpan
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 :: ColSpan -> ColSpan -> Ordering
compare :: ColSpan -> ColSpan -> Ordering
$c< :: ColSpan -> ColSpan -> Bool
< :: ColSpan -> ColSpan -> Bool
$c<= :: ColSpan -> ColSpan -> Bool
<= :: ColSpan -> ColSpan -> Bool
$c> :: ColSpan -> ColSpan -> Bool
> :: ColSpan -> ColSpan -> Bool
$c>= :: ColSpan -> ColSpan -> Bool
>= :: ColSpan -> ColSpan -> Bool
$cmax :: ColSpan -> ColSpan -> ColSpan
max :: ColSpan -> ColSpan -> ColSpan
$cmin :: ColSpan -> ColSpan -> ColSpan
min :: ColSpan -> ColSpan -> ColSpan
Ord, Int -> ColSpan -> ShowS
[ColSpan] -> ShowS
ColSpan -> String
(Int -> ColSpan -> ShowS)
-> (ColSpan -> String) -> ([ColSpan] -> ShowS) -> Show ColSpan
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColSpan -> ShowS
showsPrec :: Int -> ColSpan -> ShowS
$cshow :: ColSpan -> String
show :: ColSpan -> String
$cshowList :: [ColSpan] -> ShowS
showList :: [ColSpan] -> ShowS
Show, Typeable ColSpan
Typeable ColSpan =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpan -> c ColSpan)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpan)
-> (ColSpan -> Constr)
-> (ColSpan -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpan))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan))
-> ((forall b. Data b => b -> b) -> ColSpan -> ColSpan)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r)
-> (forall u. (forall d. Data d => d -> u) -> ColSpan -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ColSpan -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan)
-> Data ColSpan
ColSpan -> Constr
ColSpan -> DataType
(forall b. Data b => b -> b) -> ColSpan -> ColSpan
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) -> ColSpan -> u
forall u. (forall d. Data d => d -> u) -> ColSpan -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpan
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpan -> c ColSpan
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpan)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpan -> c ColSpan
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColSpan -> c ColSpan
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpan
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColSpan
$ctoConstr :: ColSpan -> Constr
toConstr :: ColSpan -> Constr
$cdataTypeOf :: ColSpan -> DataType
dataTypeOf :: ColSpan -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpan)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColSpan)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSpan)
$cgmapT :: (forall b. Data b => b -> b) -> ColSpan -> ColSpan
gmapT :: (forall b. Data b => b -> b) -> ColSpan -> ColSpan
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColSpan -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColSpan -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ColSpan -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColSpan -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColSpan -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColSpan -> m ColSpan
Data, Typeable, ReadPrec [ColSpan]
ReadPrec ColSpan
Int -> ReadS ColSpan
ReadS [ColSpan]
(Int -> ReadS ColSpan)
-> ReadS [ColSpan]
-> ReadPrec ColSpan
-> ReadPrec [ColSpan]
-> Read ColSpan
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColSpan
readsPrec :: Int -> ReadS ColSpan
$creadList :: ReadS [ColSpan]
readList :: ReadS [ColSpan]
$creadPrec :: ReadPrec ColSpan
readPrec :: ReadPrec ColSpan
$creadListPrec :: ReadPrec [ColSpan]
readListPrec :: ReadPrec [ColSpan]
Read, (forall x. ColSpan -> Rep ColSpan x)
-> (forall x. Rep ColSpan x -> ColSpan) -> Generic ColSpan
forall x. Rep ColSpan x -> ColSpan
forall x. ColSpan -> Rep ColSpan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColSpan -> Rep ColSpan x
from :: forall x. ColSpan -> Rep ColSpan x
$cto :: forall x. Rep ColSpan x -> ColSpan
to :: forall x. Rep ColSpan x -> ColSpan
Generic, Integer -> ColSpan
ColSpan -> ColSpan
ColSpan -> ColSpan -> ColSpan
(ColSpan -> ColSpan -> ColSpan)
-> (ColSpan -> ColSpan -> ColSpan)
-> (ColSpan -> ColSpan -> ColSpan)
-> (ColSpan -> ColSpan)
-> (ColSpan -> ColSpan)
-> (ColSpan -> ColSpan)
-> (Integer -> ColSpan)
-> Num ColSpan
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ColSpan -> ColSpan -> ColSpan
+ :: ColSpan -> ColSpan -> ColSpan
$c- :: ColSpan -> ColSpan -> ColSpan
- :: ColSpan -> ColSpan -> ColSpan
$c* :: ColSpan -> ColSpan -> ColSpan
* :: ColSpan -> ColSpan -> ColSpan
$cnegate :: ColSpan -> ColSpan
negate :: ColSpan -> ColSpan
$cabs :: ColSpan -> ColSpan
abs :: ColSpan -> ColSpan
$csignum :: ColSpan -> ColSpan
signum :: ColSpan -> ColSpan
$cfromInteger :: Integer -> ColSpan
fromInteger :: Integer -> ColSpan
Num)
instance Semigroup ColSpan where
ColSpan
x <> :: ColSpan -> ColSpan -> ColSpan
<> ColSpan
y =
ColSpan
x ColSpan -> ColSpan -> ColSpan
forall a. Num a => a -> a -> a
+ ColSpan
y
instance Monoid ColSpan where
mempty :: ColSpan
mempty =
ColSpan
0
instance (ColSpan ~ t) => Rewrapped ColSpan t
instance Wrapped ColSpan where
type Unwrapped ColSpan =
D.ColSpan
_Wrapped' :: Iso' ColSpan (Unwrapped ColSpan)
_Wrapped' =
(ColSpan -> ColSpan)
-> (ColSpan -> ColSpan) -> Iso ColSpan ColSpan ColSpan ColSpan
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(ColSpan ColSpan
x) -> ColSpan
x) ColSpan -> ColSpan
ColSpan
class HasColSpan a where
colSpan ::
Lens' a ColSpan
instance HasColSpan ColSpan where
colSpan :: Lens' ColSpan ColSpan
colSpan =
(ColSpan -> f ColSpan) -> ColSpan -> f ColSpan
forall a. a -> a
id
instance HasColSpan D.ColSpan where
colSpan :: Lens' ColSpan ColSpan
colSpan =
AnIso ColSpan ColSpan ColSpan ColSpan
-> Iso ColSpan ColSpan ColSpan ColSpan
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ColSpan ColSpan ColSpan ColSpan
Iso ColSpan ColSpan ColSpan ColSpan
isColSpan
class AsColSpan a where
_ColSpan ::
Prism' a ColSpan
instance AsColSpan ColSpan where
_ColSpan :: Prism' ColSpan ColSpan
_ColSpan =
p ColSpan (f ColSpan) -> p ColSpan (f ColSpan)
forall a. a -> a
id
instance AsColSpan D.ColSpan where
_ColSpan :: Prism' ColSpan ColSpan
_ColSpan =
AnIso ColSpan ColSpan ColSpan ColSpan
-> Iso ColSpan ColSpan ColSpan ColSpan
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ColSpan ColSpan ColSpan ColSpan
Iso ColSpan ColSpan ColSpan ColSpan
isColSpan
isColSpan ::
Iso'
ColSpan
D.ColSpan
isColSpan :: Iso ColSpan ColSpan ColSpan ColSpan
isColSpan =
(ColSpan -> ColSpan)
-> (ColSpan -> ColSpan) -> Iso ColSpan ColSpan ColSpan ColSpan
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(ColSpan ColSpan
x) -> ColSpan
x)
ColSpan -> ColSpan
ColSpan
instance Walkable D.ColSpan ColSpan where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ColSpan -> m ColSpan) -> ColSpan -> m ColSpan
walkM =
(ColSpan -> m ColSpan) -> ColSpan -> m ColSpan
Iso ColSpan ColSpan ColSpan ColSpan
isColSpan
query :: forall c. Monoid c => (ColSpan -> c) -> ColSpan -> c
query ColSpan -> c
f =
ColSpan -> c
f (ColSpan -> c) -> (ColSpan -> ColSpan) -> ColSpan -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ColSpan ColSpan ColSpan -> ColSpan -> ColSpan
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ColSpan ColSpan ColSpan
Iso ColSpan ColSpan ColSpan ColSpan
isColSpan
data Cell =
Cell
Attr
Alignment
RowSpan
ColSpan
[Block]
deriving (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, 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, 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, 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, Typeable, ReadPrec [Cell]
ReadPrec Cell
Int -> ReadS Cell
ReadS [Cell]
(Int -> ReadS Cell)
-> ReadS [Cell] -> ReadPrec Cell -> ReadPrec [Cell] -> Read Cell
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Cell
readsPrec :: Int -> ReadS Cell
$creadList :: ReadS [Cell]
readList :: ReadS [Cell]
$creadPrec :: ReadPrec Cell
readPrec :: ReadPrec Cell
$creadListPrec :: ReadPrec [Cell]
readListPrec :: ReadPrec [Cell]
Read, (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)
instance Semigroup Cell where
Cell Attr
a1 Alignment
l1 RowSpan
r1 ColSpan
c1 [Block]
b1 <> :: Cell -> Cell -> Cell
<> Cell Attr
a2 Alignment
l2 RowSpan
r2 ColSpan
c2 [Block]
b2 =
Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) (Alignment
l1 Alignment -> Alignment -> Alignment
forall a. Semigroup a => a -> a -> a
<> Alignment
l2) (RowSpan
r1 RowSpan -> RowSpan -> RowSpan
forall a. Semigroup a => a -> a -> a
<> RowSpan
r2) (ColSpan
c1 ColSpan -> ColSpan -> ColSpan
forall a. Semigroup a => a -> a -> a
<> ColSpan
c2) ([Block]
b1 [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
b2)
instance Monoid Cell where
mempty :: Cell
mempty =
Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
forall a. Monoid a => a
mempty Alignment
forall a. Monoid a => a
mempty RowSpan
forall a. Monoid a => a
mempty ColSpan
forall a. Monoid a => a
mempty [Block]
forall a. Monoid a => a
mempty
class HasCell a where
cell ::
Lens' a Cell
instance HasCell Cell where
cell :: Lens' Cell Cell
cell =
(Cell -> f Cell) -> Cell -> f Cell
forall a. a -> a
id
instance HasBlocks Cell where
blocks :: Lens' Cell [Block]
blocks [Block] -> f [Block]
f (Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) =
([Block] -> Cell) -> f [Block] -> f Cell
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a Alignment
l RowSpan
r ColSpan
c) ([Block] -> f [Block]
f [Block]
b)
instance HasAttr Cell where
attr :: Lens' Cell Attr
attr Attr -> f Attr
f (Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) =
(Attr -> Cell) -> f Attr -> f Cell
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a' Alignment
l RowSpan
r ColSpan
c [Block]
b) (Attr -> f Attr
f Attr
a)
instance HasAlignment Cell where
alignment :: Lens' Cell Alignment
alignment Alignment -> f Alignment
f (Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) =
(Alignment -> Cell) -> f Alignment -> f Cell
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Alignment
l' -> Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a Alignment
l' RowSpan
r ColSpan
c [Block]
b) (Alignment -> f Alignment
f Alignment
l)
instance HasRowSpan Cell where
rowSpan :: Lens' Cell RowSpan
rowSpan RowSpan -> f RowSpan
f (Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) =
(RowSpan -> Cell) -> f RowSpan -> f Cell
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\RowSpan
r' -> Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a Alignment
l RowSpan
r' ColSpan
c [Block]
b) (RowSpan -> f RowSpan
f RowSpan
r)
instance HasColSpan Cell where
colSpan :: Lens' Cell ColSpan
colSpan ColSpan -> f ColSpan
f (Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) =
(ColSpan -> Cell) -> f ColSpan -> f Cell
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ColSpan
c' -> Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
a Alignment
l RowSpan
r ColSpan
c' [Block]
b) (ColSpan -> f ColSpan
f ColSpan
c)
instance HasCell D.Cell where
cell :: Lens' Cell Cell
cell =
AnIso Cell Cell Cell Cell -> Iso Cell Cell Cell Cell
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Cell Cell Cell Cell
Iso' Cell Cell
isCell
class AsCell a where
_Cell ::
Prism' a Cell
instance AsCell Cell where
_Cell :: Prism' Cell Cell
_Cell =
p Cell (f Cell) -> p Cell (f Cell)
forall a. a -> a
id
instance AsCell D.Cell where
_Cell :: Prism' Cell Cell
_Cell =
AnIso Cell Cell Cell Cell -> Iso Cell Cell Cell Cell
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Cell Cell Cell Cell
Iso' Cell Cell
isCell
isCell ::
Iso'
Cell
D.Cell
isCell :: Iso' Cell Cell
isCell =
(Cell -> Cell) -> (Cell -> Cell) -> Iso' Cell Cell
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) -> Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
D.Cell (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) (Getting Alignment Alignment Alignment -> Alignment -> Alignment
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Alignment Alignment Alignment
Iso' Alignment Alignment
isAlignment Alignment
l) (Getting RowSpan RowSpan RowSpan -> RowSpan -> RowSpan
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting RowSpan RowSpan RowSpan
Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan RowSpan
r) (Getting ColSpan ColSpan ColSpan -> ColSpan -> ColSpan
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ColSpan ColSpan ColSpan
Iso ColSpan ColSpan ColSpan ColSpan
isColSpan ColSpan
c) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b))
(\(D.Cell Attr
a Alignment
l RowSpan
r ColSpan
c [Block]
b) -> Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) (AReview Alignment Alignment -> Alignment -> Alignment
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Alignment Alignment
Iso' Alignment Alignment
isAlignment Alignment
l) (AReview RowSpan RowSpan -> RowSpan -> RowSpan
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview RowSpan RowSpan
Iso RowSpan RowSpan RowSpan RowSpan
isRowSpan RowSpan
r) (AReview ColSpan ColSpan -> ColSpan -> ColSpan
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ColSpan ColSpan
Iso ColSpan ColSpan ColSpan ColSpan
isColSpan ColSpan
c) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b))
instance Walkable D.Cell Cell where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Cell -> m Cell) -> Cell -> m Cell
walkM =
(Cell -> m Cell) -> Cell -> m Cell
Iso' Cell Cell
isCell
query :: forall c. Monoid c => (Cell -> c) -> Cell -> c
query Cell -> c
f =
Cell -> c
f (Cell -> c) -> (Cell -> Cell) -> Cell -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Cell Cell Cell -> Cell -> Cell
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Cell Cell Cell
Iso' Cell Cell
isCell
data Row =
Row
Attr
[Cell]
deriving (Row -> Row -> Bool
(Row -> Row -> Bool) -> (Row -> Row -> Bool) -> Eq Row
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Row -> Row -> Bool
== :: Row -> Row -> Bool
$c/= :: Row -> Row -> Bool
/= :: Row -> Row -> Bool
Eq, Eq Row
Eq Row =>
(Row -> Row -> Ordering)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Row)
-> (Row -> Row -> Row)
-> Ord Row
Row -> Row -> Bool
Row -> Row -> Ordering
Row -> Row -> Row
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 :: Row -> Row -> Ordering
compare :: Row -> Row -> Ordering
$c< :: Row -> Row -> Bool
< :: Row -> Row -> Bool
$c<= :: Row -> Row -> Bool
<= :: Row -> Row -> Bool
$c> :: Row -> Row -> Bool
> :: Row -> Row -> Bool
$c>= :: Row -> Row -> Bool
>= :: Row -> Row -> Bool
$cmax :: Row -> Row -> Row
max :: Row -> Row -> Row
$cmin :: Row -> Row -> Row
min :: Row -> Row -> Row
Ord, Int -> Row -> ShowS
[Row] -> ShowS
Row -> String
(Int -> Row -> ShowS)
-> (Row -> String) -> ([Row] -> ShowS) -> Show Row
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Row -> ShowS
showsPrec :: Int -> Row -> ShowS
$cshow :: Row -> String
show :: Row -> String
$cshowList :: [Row] -> ShowS
showList :: [Row] -> ShowS
Show, Typeable Row
Typeable Row =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Row -> c Row)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Row)
-> (Row -> Constr)
-> (Row -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Row))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row))
-> ((forall b. Data b => b -> b) -> Row -> Row)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r)
-> (forall u. (forall d. Data d => d -> u) -> Row -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Row -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Row -> m Row)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row)
-> Data Row
Row -> Constr
Row -> DataType
(forall b. Data b => b -> b) -> Row -> Row
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) -> Row -> u
forall u. (forall d. Data d => d -> u) -> Row -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Row -> m Row
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Row
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Row -> c Row
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Row)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Row -> c Row
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Row -> c Row
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Row
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Row
$ctoConstr :: Row -> Constr
toConstr :: Row -> Constr
$cdataTypeOf :: Row -> DataType
dataTypeOf :: Row -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Row)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Row)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Row)
$cgmapT :: (forall b. Data b => b -> b) -> Row -> Row
gmapT :: (forall b. Data b => b -> b) -> Row -> Row
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Row -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Row -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Row -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Row -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Row -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Row -> m Row
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Row -> m Row
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Row -> m Row
Data, Typeable, ReadPrec [Row]
ReadPrec Row
Int -> ReadS Row
ReadS [Row]
(Int -> ReadS Row)
-> ReadS [Row] -> ReadPrec Row -> ReadPrec [Row] -> Read Row
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Row
readsPrec :: Int -> ReadS Row
$creadList :: ReadS [Row]
readList :: ReadS [Row]
$creadPrec :: ReadPrec Row
readPrec :: ReadPrec Row
$creadListPrec :: ReadPrec [Row]
readListPrec :: ReadPrec [Row]
Read, (forall x. Row -> Rep Row x)
-> (forall x. Rep Row x -> Row) -> Generic Row
forall x. Rep Row x -> Row
forall x. Row -> Rep Row x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Row -> Rep Row x
from :: forall x. Row -> Rep Row x
$cto :: forall x. Rep Row x -> Row
to :: forall x. Rep Row x -> Row
Generic)
instance Semigroup Row where
Row Attr
a1 [Cell]
c1 <> :: Row -> Row -> Row
<> Row Attr
a2 [Cell]
c2 =
Attr -> [Cell] -> Row
Row (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) ([Cell]
c1 [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> [Cell]
c2)
instance Monoid Row where
mempty :: Row
mempty =
Attr -> [Cell] -> Row
Row Attr
forall a. Monoid a => a
mempty [Cell]
forall a. Monoid a => a
mempty
class HasRow a where
row ::
Lens' a Row
rowCells ::
Lens' a [Cell]
rowCells =
(Row -> f Row) -> a -> f a
forall a. HasRow a => Lens' a Row
Lens' a Row
row ((Row -> f Row) -> a -> f a)
-> (([Cell] -> f [Cell]) -> Row -> f Row)
-> ([Cell] -> f [Cell])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Cell] -> f [Cell]) -> Row -> f Row
forall a. HasRow a => Lens' a [Cell]
Lens' Row [Cell]
rowCells
instance HasRow Row where
row :: Lens' Row Row
row =
(Row -> f Row) -> Row -> f Row
forall a. a -> a
id
rowCells :: Lens' Row [Cell]
rowCells [Cell] -> f [Cell]
f (Row Attr
a [Cell]
c) =
([Cell] -> Row) -> f [Cell] -> f Row
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Cell] -> Row
Row Attr
a) ([Cell] -> f [Cell]
f [Cell]
c)
instance HasAttr Row where
attr :: Lens' Row Attr
attr Attr -> f Attr
f (Row Attr
a [Cell]
c) =
(Attr -> Row) -> f Attr -> f Row
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Cell] -> Row
`Row` [Cell]
c) (Attr -> f Attr
f Attr
a)
instance HasRow D.Row where
row :: Lens' Row Row
row =
AnIso Row Row Row Row -> Iso Row Row Row Row
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Row Row Row Row
Iso' Row Row
isRow
class AsRow a where
_Row ::
Prism' a Row
instance AsRow Row where
_Row :: Prism' Row Row
_Row =
p Row (f Row) -> p Row (f Row)
forall a. a -> a
id
instance AsRow D.Row where
_Row :: Prism' Row Row
_Row =
AnIso Row Row Row Row -> Iso Row Row Row Row
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Row Row Row Row
Iso' Row Row
isRow
isRow ::
Iso'
Row
D.Row
isRow :: Iso' Row Row
isRow =
(Row -> Row) -> (Row -> Row) -> Iso' Row Row
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Row Attr
a [Cell]
c) -> Attr -> [Cell] -> Row
D.Row (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Cell -> Cell) -> [Cell] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Cell Cell Cell -> Cell -> Cell
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Cell Cell Cell
Iso' Cell Cell
isCell) [Cell]
c))
(\(D.Row Attr
a [Cell]
c) -> Attr -> [Cell] -> Row
Row (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Cell -> Cell) -> [Cell] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Cell Cell -> Cell -> Cell
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Cell Cell
Iso' Cell Cell
isCell) [Cell]
c))
instance Walkable D.Row Row where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Row -> m Row) -> Row -> m Row
walkM =
(Row -> m Row) -> Row -> m Row
Iso' Row Row
isRow
query :: forall c. Monoid c => (Row -> c) -> Row -> c
query Row -> c
f =
Row -> c
f (Row -> c) -> (Row -> Row) -> Row -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Row Row Row -> Row -> Row
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Row Row Row
Iso' Row Row
isRow
data TableHead =
TableHead Attr [Row]
deriving (TableHead -> TableHead -> Bool
(TableHead -> TableHead -> Bool)
-> (TableHead -> TableHead -> Bool) -> Eq TableHead
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TableHead -> TableHead -> Bool
== :: TableHead -> TableHead -> Bool
$c/= :: TableHead -> TableHead -> Bool
/= :: TableHead -> TableHead -> Bool
Eq, Eq TableHead
Eq TableHead =>
(TableHead -> TableHead -> Ordering)
-> (TableHead -> TableHead -> Bool)
-> (TableHead -> TableHead -> Bool)
-> (TableHead -> TableHead -> Bool)
-> (TableHead -> TableHead -> Bool)
-> (TableHead -> TableHead -> TableHead)
-> (TableHead -> TableHead -> TableHead)
-> Ord TableHead
TableHead -> TableHead -> Bool
TableHead -> TableHead -> Ordering
TableHead -> TableHead -> TableHead
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 :: TableHead -> TableHead -> Ordering
compare :: TableHead -> TableHead -> Ordering
$c< :: TableHead -> TableHead -> Bool
< :: TableHead -> TableHead -> Bool
$c<= :: TableHead -> TableHead -> Bool
<= :: TableHead -> TableHead -> Bool
$c> :: TableHead -> TableHead -> Bool
> :: TableHead -> TableHead -> Bool
$c>= :: TableHead -> TableHead -> Bool
>= :: TableHead -> TableHead -> Bool
$cmax :: TableHead -> TableHead -> TableHead
max :: TableHead -> TableHead -> TableHead
$cmin :: TableHead -> TableHead -> TableHead
min :: TableHead -> TableHead -> TableHead
Ord, Int -> TableHead -> ShowS
[TableHead] -> ShowS
TableHead -> String
(Int -> TableHead -> ShowS)
-> (TableHead -> String)
-> ([TableHead] -> ShowS)
-> Show TableHead
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TableHead -> ShowS
showsPrec :: Int -> TableHead -> ShowS
$cshow :: TableHead -> String
show :: TableHead -> String
$cshowList :: [TableHead] -> ShowS
showList :: [TableHead] -> ShowS
Show, Typeable TableHead
Typeable TableHead =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableHead -> c TableHead)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableHead)
-> (TableHead -> Constr)
-> (TableHead -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableHead))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead))
-> ((forall b. Data b => b -> b) -> TableHead -> TableHead)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r)
-> (forall u. (forall d. Data d => d -> u) -> TableHead -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TableHead -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead)
-> Data TableHead
TableHead -> Constr
TableHead -> DataType
(forall b. Data b => b -> b) -> TableHead -> TableHead
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) -> TableHead -> u
forall u. (forall d. Data d => d -> u) -> TableHead -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableHead
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableHead -> c TableHead
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableHead)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableHead -> c TableHead
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableHead -> c TableHead
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableHead
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableHead
$ctoConstr :: TableHead -> Constr
toConstr :: TableHead -> Constr
$cdataTypeOf :: TableHead -> DataType
dataTypeOf :: TableHead -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableHead)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableHead)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead)
$cgmapT :: (forall b. Data b => b -> b) -> TableHead -> TableHead
gmapT :: (forall b. Data b => b -> b) -> TableHead -> TableHead
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableHead -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableHead -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TableHead -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableHead -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableHead -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableHead -> m TableHead
Data, Typeable, ReadPrec [TableHead]
ReadPrec TableHead
Int -> ReadS TableHead
ReadS [TableHead]
(Int -> ReadS TableHead)
-> ReadS [TableHead]
-> ReadPrec TableHead
-> ReadPrec [TableHead]
-> Read TableHead
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TableHead
readsPrec :: Int -> ReadS TableHead
$creadList :: ReadS [TableHead]
readList :: ReadS [TableHead]
$creadPrec :: ReadPrec TableHead
readPrec :: ReadPrec TableHead
$creadListPrec :: ReadPrec [TableHead]
readListPrec :: ReadPrec [TableHead]
Read, (forall x. TableHead -> Rep TableHead x)
-> (forall x. Rep TableHead x -> TableHead) -> Generic TableHead
forall x. Rep TableHead x -> TableHead
forall x. TableHead -> Rep TableHead x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TableHead -> Rep TableHead x
from :: forall x. TableHead -> Rep TableHead x
$cto :: forall x. Rep TableHead x -> TableHead
to :: forall x. Rep TableHead x -> TableHead
Generic)
instance Semigroup TableHead where
TableHead Attr
a1 [Row]
r1 <> :: TableHead -> TableHead -> TableHead
<> TableHead Attr
a2 [Row]
r2 =
Attr -> [Row] -> TableHead
TableHead (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) ([Row]
r1 [Row] -> [Row] -> [Row]
forall a. Semigroup a => a -> a -> a
<> [Row]
r2)
instance Monoid TableHead where
mempty :: TableHead
mempty =
Attr -> [Row] -> TableHead
TableHead Attr
forall a. Monoid a => a
mempty [Row]
forall a. Monoid a => a
mempty
class HasTableHead a where
tableHead ::
Lens' a TableHead
tableHeadRows ::
Lens' a [Row]
tableHeadRows =
(TableHead -> f TableHead) -> a -> f a
forall a. HasTableHead a => Lens' a TableHead
Lens' a TableHead
tableHead ((TableHead -> f TableHead) -> a -> f a)
-> (([Row] -> f [Row]) -> TableHead -> f TableHead)
-> ([Row] -> f [Row])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Row] -> f [Row]) -> TableHead -> f TableHead
forall a. HasTableHead a => Lens' a [Row]
Lens' TableHead [Row]
tableHeadRows
instance HasTableHead TableHead where
tableHead :: Lens' TableHead TableHead
tableHead =
(TableHead -> f TableHead) -> TableHead -> f TableHead
forall a. a -> a
id
tableHeadRows :: Lens' TableHead [Row]
tableHeadRows [Row] -> f [Row]
f (TableHead Attr
a [Row]
r) =
([Row] -> TableHead) -> f [Row] -> f TableHead
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Row] -> TableHead
TableHead Attr
a) ([Row] -> f [Row]
f [Row]
r)
instance HasAttr TableHead where
attr :: Lens' TableHead Attr
attr Attr -> f Attr
f (TableHead Attr
a [Row]
r) =
(Attr -> TableHead) -> f Attr -> f TableHead
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Row] -> TableHead
`TableHead` [Row]
r) (Attr -> f Attr
f Attr
a)
instance HasTableHead D.TableHead where
tableHead :: Lens' TableHead TableHead
tableHead =
AnIso TableHead TableHead TableHead TableHead
-> Iso TableHead TableHead TableHead TableHead
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso TableHead TableHead TableHead TableHead
Iso' TableHead TableHead
isTableHead
class AsTableHead a where
_TableHead ::
Prism' a TableHead
instance AsTableHead TableHead where
_TableHead :: Prism' TableHead TableHead
_TableHead =
p TableHead (f TableHead) -> p TableHead (f TableHead)
forall a. a -> a
id
instance AsTableHead D.TableHead where
_TableHead :: Prism' TableHead TableHead
_TableHead =
AnIso TableHead TableHead TableHead TableHead
-> Iso TableHead TableHead TableHead TableHead
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso TableHead TableHead TableHead TableHead
Iso' TableHead TableHead
isTableHead
isTableHead ::
Iso'
TableHead
D.TableHead
isTableHead :: Iso' TableHead TableHead
isTableHead =
(TableHead -> TableHead)
-> (TableHead -> TableHead) -> Iso' TableHead TableHead
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(TableHead Attr
a [Row]
r) -> Attr -> [Row] -> TableHead
D.TableHead (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Row Row Row -> Row -> Row
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Row Row Row
Iso' Row Row
isRow) [Row]
r))
(\(D.TableHead Attr
a [Row]
r) -> Attr -> [Row] -> TableHead
TableHead (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Row Row -> Row -> Row
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Row Row
Iso' Row Row
isRow) [Row]
r))
instance Walkable D.TableHead TableHead where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(TableHead -> m TableHead) -> TableHead -> m TableHead
walkM =
(TableHead -> m TableHead) -> TableHead -> m TableHead
Iso' TableHead TableHead
isTableHead
query :: forall c. Monoid c => (TableHead -> c) -> TableHead -> c
query TableHead -> c
f =
TableHead -> c
f (TableHead -> c) -> (TableHead -> TableHead) -> TableHead -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting TableHead TableHead TableHead -> TableHead -> TableHead
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting TableHead TableHead TableHead
Iso' TableHead TableHead
isTableHead
newtype RowHeadColumns =
RowHeadColumns D.RowHeadColumns
deriving (RowHeadColumns -> RowHeadColumns -> Bool
(RowHeadColumns -> RowHeadColumns -> Bool)
-> (RowHeadColumns -> RowHeadColumns -> Bool) -> Eq RowHeadColumns
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RowHeadColumns -> RowHeadColumns -> Bool
== :: RowHeadColumns -> RowHeadColumns -> Bool
$c/= :: RowHeadColumns -> RowHeadColumns -> Bool
/= :: RowHeadColumns -> RowHeadColumns -> Bool
Eq, Eq RowHeadColumns
Eq RowHeadColumns =>
(RowHeadColumns -> RowHeadColumns -> Ordering)
-> (RowHeadColumns -> RowHeadColumns -> Bool)
-> (RowHeadColumns -> RowHeadColumns -> Bool)
-> (RowHeadColumns -> RowHeadColumns -> Bool)
-> (RowHeadColumns -> RowHeadColumns -> Bool)
-> (RowHeadColumns -> RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns -> RowHeadColumns)
-> Ord RowHeadColumns
RowHeadColumns -> RowHeadColumns -> Bool
RowHeadColumns -> RowHeadColumns -> Ordering
RowHeadColumns -> RowHeadColumns -> RowHeadColumns
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 :: RowHeadColumns -> RowHeadColumns -> Ordering
compare :: RowHeadColumns -> RowHeadColumns -> Ordering
$c< :: RowHeadColumns -> RowHeadColumns -> Bool
< :: RowHeadColumns -> RowHeadColumns -> Bool
$c<= :: RowHeadColumns -> RowHeadColumns -> Bool
<= :: RowHeadColumns -> RowHeadColumns -> Bool
$c> :: RowHeadColumns -> RowHeadColumns -> Bool
> :: RowHeadColumns -> RowHeadColumns -> Bool
$c>= :: RowHeadColumns -> RowHeadColumns -> Bool
>= :: RowHeadColumns -> RowHeadColumns -> Bool
$cmax :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
max :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
$cmin :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
min :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
Ord, Int -> RowHeadColumns -> ShowS
[RowHeadColumns] -> ShowS
RowHeadColumns -> String
(Int -> RowHeadColumns -> ShowS)
-> (RowHeadColumns -> String)
-> ([RowHeadColumns] -> ShowS)
-> Show RowHeadColumns
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RowHeadColumns -> ShowS
showsPrec :: Int -> RowHeadColumns -> ShowS
$cshow :: RowHeadColumns -> String
show :: RowHeadColumns -> String
$cshowList :: [RowHeadColumns] -> ShowS
showList :: [RowHeadColumns] -> ShowS
Show, Typeable RowHeadColumns
Typeable RowHeadColumns =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowHeadColumns)
-> (RowHeadColumns -> Constr)
-> (RowHeadColumns -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RowHeadColumns))
-> ((forall b. Data b => b -> b)
-> RowHeadColumns -> RowHeadColumns)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r)
-> (forall u.
(forall d. Data d => d -> u) -> RowHeadColumns -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RowHeadColumns -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns)
-> Data RowHeadColumns
RowHeadColumns -> Constr
RowHeadColumns -> DataType
(forall b. Data b => b -> b) -> RowHeadColumns -> RowHeadColumns
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) -> RowHeadColumns -> u
forall u. (forall d. Data d => d -> u) -> RowHeadColumns -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowHeadColumns
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RowHeadColumns)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowHeadColumns -> c RowHeadColumns
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowHeadColumns
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowHeadColumns
$ctoConstr :: RowHeadColumns -> Constr
toConstr :: RowHeadColumns -> Constr
$cdataTypeOf :: RowHeadColumns -> DataType
dataTypeOf :: RowHeadColumns -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowHeadColumns)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RowHeadColumns)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RowHeadColumns)
$cgmapT :: (forall b. Data b => b -> b) -> RowHeadColumns -> RowHeadColumns
gmapT :: (forall b. Data b => b -> b) -> RowHeadColumns -> RowHeadColumns
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowHeadColumns -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RowHeadColumns -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RowHeadColumns -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RowHeadColumns -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> RowHeadColumns -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> RowHeadColumns -> m RowHeadColumns
Data, Typeable, ReadPrec [RowHeadColumns]
ReadPrec RowHeadColumns
Int -> ReadS RowHeadColumns
ReadS [RowHeadColumns]
(Int -> ReadS RowHeadColumns)
-> ReadS [RowHeadColumns]
-> ReadPrec RowHeadColumns
-> ReadPrec [RowHeadColumns]
-> Read RowHeadColumns
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RowHeadColumns
readsPrec :: Int -> ReadS RowHeadColumns
$creadList :: ReadS [RowHeadColumns]
readList :: ReadS [RowHeadColumns]
$creadPrec :: ReadPrec RowHeadColumns
readPrec :: ReadPrec RowHeadColumns
$creadListPrec :: ReadPrec [RowHeadColumns]
readListPrec :: ReadPrec [RowHeadColumns]
Read, (forall x. RowHeadColumns -> Rep RowHeadColumns x)
-> (forall x. Rep RowHeadColumns x -> RowHeadColumns)
-> Generic RowHeadColumns
forall x. Rep RowHeadColumns x -> RowHeadColumns
forall x. RowHeadColumns -> Rep RowHeadColumns x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RowHeadColumns -> Rep RowHeadColumns x
from :: forall x. RowHeadColumns -> Rep RowHeadColumns x
$cto :: forall x. Rep RowHeadColumns x -> RowHeadColumns
to :: forall x. Rep RowHeadColumns x -> RowHeadColumns
Generic, Integer -> RowHeadColumns
RowHeadColumns -> RowHeadColumns
RowHeadColumns -> RowHeadColumns -> RowHeadColumns
(RowHeadColumns -> RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns)
-> (Integer -> RowHeadColumns)
-> Num RowHeadColumns
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
+ :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
$c- :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
- :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
$c* :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
* :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
$cnegate :: RowHeadColumns -> RowHeadColumns
negate :: RowHeadColumns -> RowHeadColumns
$cabs :: RowHeadColumns -> RowHeadColumns
abs :: RowHeadColumns -> RowHeadColumns
$csignum :: RowHeadColumns -> RowHeadColumns
signum :: RowHeadColumns -> RowHeadColumns
$cfromInteger :: Integer -> RowHeadColumns
fromInteger :: Integer -> RowHeadColumns
Num)
instance Semigroup RowHeadColumns where
RowHeadColumns
x <> :: RowHeadColumns -> RowHeadColumns -> RowHeadColumns
<> RowHeadColumns
y =
RowHeadColumns
x RowHeadColumns -> RowHeadColumns -> RowHeadColumns
forall a. Num a => a -> a -> a
+ RowHeadColumns
y
instance Monoid RowHeadColumns where
mempty :: RowHeadColumns
mempty =
RowHeadColumns
0
instance (RowHeadColumns ~ t) => Rewrapped RowHeadColumns t
instance Wrapped RowHeadColumns where
type Unwrapped RowHeadColumns =
D.RowHeadColumns
_Wrapped' :: Iso' RowHeadColumns (Unwrapped RowHeadColumns)
_Wrapped' =
(RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns)
-> Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(RowHeadColumns RowHeadColumns
x) -> RowHeadColumns
x) RowHeadColumns -> RowHeadColumns
RowHeadColumns
class HasRowHeadColumns a where
rowHeadColumns ::
Lens' a RowHeadColumns
instance HasRowHeadColumns RowHeadColumns where
rowHeadColumns :: Lens' RowHeadColumns RowHeadColumns
rowHeadColumns =
(RowHeadColumns -> f RowHeadColumns)
-> RowHeadColumns -> f RowHeadColumns
forall a. a -> a
id
instance HasRowHeadColumns D.RowHeadColumns where
rowHeadColumns :: Lens' RowHeadColumns RowHeadColumns
rowHeadColumns =
AnIso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
-> Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns
class AsRowHeadColumns a where
_RowHeadColumns ::
Prism' a RowHeadColumns
instance AsRowHeadColumns RowHeadColumns where
_RowHeadColumns :: Prism' RowHeadColumns RowHeadColumns
_RowHeadColumns =
p RowHeadColumns (f RowHeadColumns)
-> p RowHeadColumns (f RowHeadColumns)
forall a. a -> a
id
instance AsRowHeadColumns D.RowHeadColumns where
_RowHeadColumns :: Prism' RowHeadColumns RowHeadColumns
_RowHeadColumns =
AnIso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
-> Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns
isRowHeadColumns ::
Iso'
RowHeadColumns
D.RowHeadColumns
isRowHeadColumns :: Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns =
(RowHeadColumns -> RowHeadColumns)
-> (RowHeadColumns -> RowHeadColumns)
-> Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(RowHeadColumns RowHeadColumns
x) -> RowHeadColumns
x)
RowHeadColumns -> RowHeadColumns
RowHeadColumns
instance Walkable D.RowHeadColumns RowHeadColumns where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(RowHeadColumns -> m RowHeadColumns)
-> RowHeadColumns -> m RowHeadColumns
walkM =
(RowHeadColumns -> m RowHeadColumns)
-> RowHeadColumns -> m RowHeadColumns
Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns
query :: forall c. Monoid c => (RowHeadColumns -> c) -> RowHeadColumns -> c
query RowHeadColumns -> c
f =
RowHeadColumns -> c
f (RowHeadColumns -> c)
-> (RowHeadColumns -> RowHeadColumns) -> RowHeadColumns -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting RowHeadColumns RowHeadColumns RowHeadColumns
-> RowHeadColumns -> RowHeadColumns
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting RowHeadColumns RowHeadColumns RowHeadColumns
Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns
data TableBody =
TableBody
Attr
RowHeadColumns
[Row]
[Row]
deriving (TableBody -> TableBody -> Bool
(TableBody -> TableBody -> Bool)
-> (TableBody -> TableBody -> Bool) -> Eq TableBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TableBody -> TableBody -> Bool
== :: TableBody -> TableBody -> Bool
$c/= :: TableBody -> TableBody -> Bool
/= :: TableBody -> TableBody -> Bool
Eq, Eq TableBody
Eq TableBody =>
(TableBody -> TableBody -> Ordering)
-> (TableBody -> TableBody -> Bool)
-> (TableBody -> TableBody -> Bool)
-> (TableBody -> TableBody -> Bool)
-> (TableBody -> TableBody -> Bool)
-> (TableBody -> TableBody -> TableBody)
-> (TableBody -> TableBody -> TableBody)
-> Ord TableBody
TableBody -> TableBody -> Bool
TableBody -> TableBody -> Ordering
TableBody -> TableBody -> TableBody
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 :: TableBody -> TableBody -> Ordering
compare :: TableBody -> TableBody -> Ordering
$c< :: TableBody -> TableBody -> Bool
< :: TableBody -> TableBody -> Bool
$c<= :: TableBody -> TableBody -> Bool
<= :: TableBody -> TableBody -> Bool
$c> :: TableBody -> TableBody -> Bool
> :: TableBody -> TableBody -> Bool
$c>= :: TableBody -> TableBody -> Bool
>= :: TableBody -> TableBody -> Bool
$cmax :: TableBody -> TableBody -> TableBody
max :: TableBody -> TableBody -> TableBody
$cmin :: TableBody -> TableBody -> TableBody
min :: TableBody -> TableBody -> TableBody
Ord, Int -> TableBody -> ShowS
[TableBody] -> ShowS
TableBody -> String
(Int -> TableBody -> ShowS)
-> (TableBody -> String)
-> ([TableBody] -> ShowS)
-> Show TableBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TableBody -> ShowS
showsPrec :: Int -> TableBody -> ShowS
$cshow :: TableBody -> String
show :: TableBody -> String
$cshowList :: [TableBody] -> ShowS
showList :: [TableBody] -> ShowS
Show, Typeable TableBody
Typeable TableBody =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableBody -> c TableBody)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableBody)
-> (TableBody -> Constr)
-> (TableBody -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableBody))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody))
-> ((forall b. Data b => b -> b) -> TableBody -> TableBody)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r)
-> (forall u. (forall d. Data d => d -> u) -> TableBody -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TableBody -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody)
-> Data TableBody
TableBody -> Constr
TableBody -> DataType
(forall b. Data b => b -> b) -> TableBody -> TableBody
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) -> TableBody -> u
forall u. (forall d. Data d => d -> u) -> TableBody -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableBody
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableBody -> c TableBody
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableBody)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableBody -> c TableBody
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableBody -> c TableBody
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableBody
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableBody
$ctoConstr :: TableBody -> Constr
toConstr :: TableBody -> Constr
$cdataTypeOf :: TableBody -> DataType
dataTypeOf :: TableBody -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableBody)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableBody)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody)
$cgmapT :: (forall b. Data b => b -> b) -> TableBody -> TableBody
gmapT :: (forall b. Data b => b -> b) -> TableBody -> TableBody
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableBody -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableBody -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TableBody -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableBody -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableBody -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableBody -> m TableBody
Data, Typeable, ReadPrec [TableBody]
ReadPrec TableBody
Int -> ReadS TableBody
ReadS [TableBody]
(Int -> ReadS TableBody)
-> ReadS [TableBody]
-> ReadPrec TableBody
-> ReadPrec [TableBody]
-> Read TableBody
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TableBody
readsPrec :: Int -> ReadS TableBody
$creadList :: ReadS [TableBody]
readList :: ReadS [TableBody]
$creadPrec :: ReadPrec TableBody
readPrec :: ReadPrec TableBody
$creadListPrec :: ReadPrec [TableBody]
readListPrec :: ReadPrec [TableBody]
Read, (forall x. TableBody -> Rep TableBody x)
-> (forall x. Rep TableBody x -> TableBody) -> Generic TableBody
forall x. Rep TableBody x -> TableBody
forall x. TableBody -> Rep TableBody x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TableBody -> Rep TableBody x
from :: forall x. TableBody -> Rep TableBody x
$cto :: forall x. Rep TableBody x -> TableBody
to :: forall x. Rep TableBody x -> TableBody
Generic)
instance Semigroup TableBody where
TableBody Attr
a1 RowHeadColumns
c1 [Row]
r1 [Row]
s1 <> :: TableBody -> TableBody -> TableBody
<> TableBody Attr
a2 RowHeadColumns
c2 [Row]
r2 [Row]
s2 =
Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) (RowHeadColumns
c1 RowHeadColumns -> RowHeadColumns -> RowHeadColumns
forall a. Semigroup a => a -> a -> a
<> RowHeadColumns
c2) ([Row]
r1 [Row] -> [Row] -> [Row]
forall a. Semigroup a => a -> a -> a
<> [Row]
r2) ([Row]
s1 [Row] -> [Row] -> [Row]
forall a. Semigroup a => a -> a -> a
<> [Row]
s2)
instance Monoid TableBody where
mempty :: TableBody
mempty =
Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
forall a. Monoid a => a
mempty RowHeadColumns
forall a. Monoid a => a
mempty [Row]
forall a. Monoid a => a
mempty [Row]
forall a. Monoid a => a
mempty
class HasTableBody a where
tableBody ::
Lens' a TableBody
tableBodyRows1 ::
Lens' a [Row]
tableBodyRows1 =
(TableBody -> f TableBody) -> a -> f a
forall a. HasTableBody a => Lens' a TableBody
Lens' a TableBody
tableBody ((TableBody -> f TableBody) -> a -> f a)
-> (([Row] -> f [Row]) -> TableBody -> f TableBody)
-> ([Row] -> f [Row])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Row] -> f [Row]) -> TableBody -> f TableBody
forall a. HasTableBody a => Lens' a [Row]
Lens' TableBody [Row]
tableBodyRows1
tableBodyRows2 ::
Lens' a [Row]
tableBodyRows2 =
(TableBody -> f TableBody) -> a -> f a
forall a. HasTableBody a => Lens' a TableBody
Lens' a TableBody
tableBody ((TableBody -> f TableBody) -> a -> f a)
-> (([Row] -> f [Row]) -> TableBody -> f TableBody)
-> ([Row] -> f [Row])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Row] -> f [Row]) -> TableBody -> f TableBody
forall a. HasTableBody a => Lens' a [Row]
Lens' TableBody [Row]
tableBodyRows2
instance HasTableBody TableBody where
tableBody :: Lens' TableBody TableBody
tableBody =
(TableBody -> f TableBody) -> TableBody -> f TableBody
forall a. a -> a
id
tableBodyRows1 :: Lens' TableBody [Row]
tableBodyRows1 [Row] -> f [Row]
f (TableBody Attr
a RowHeadColumns
c [Row]
r1 [Row]
r2) =
([Row] -> TableBody) -> f [Row] -> f TableBody
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Row]
r1' -> Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
a RowHeadColumns
c [Row]
r1' [Row]
r2) ([Row] -> f [Row]
f [Row]
r1)
tableBodyRows2 :: Lens' TableBody [Row]
tableBodyRows2 [Row] -> f [Row]
f (TableBody Attr
a RowHeadColumns
c [Row]
r1 [Row]
r2) =
([Row] -> TableBody) -> f [Row] -> f TableBody
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
a RowHeadColumns
c [Row]
r1) ([Row] -> f [Row]
f [Row]
r2)
instance HasAttr TableBody where
attr :: Lens' TableBody Attr
attr Attr -> f Attr
f (TableBody Attr
a RowHeadColumns
c [Row]
r1 [Row]
r2) =
(Attr -> TableBody) -> f Attr -> f TableBody
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
a' RowHeadColumns
c [Row]
r1 [Row]
r2) (Attr -> f Attr
f Attr
a)
instance HasRowHeadColumns TableBody where
rowHeadColumns :: Lens' TableBody RowHeadColumns
rowHeadColumns RowHeadColumns -> f RowHeadColumns
f (TableBody Attr
a RowHeadColumns
c [Row]
r1 [Row]
r2) =
(RowHeadColumns -> TableBody) -> f RowHeadColumns -> f TableBody
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\RowHeadColumns
c' -> Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
a RowHeadColumns
c' [Row]
r1 [Row]
r2) (RowHeadColumns -> f RowHeadColumns
f RowHeadColumns
c)
instance HasTableBody D.TableBody where
tableBody :: Lens' TableBody TableBody
tableBody =
AnIso TableBody TableBody TableBody TableBody
-> Iso TableBody TableBody TableBody TableBody
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso TableBody TableBody TableBody TableBody
Iso' TableBody TableBody
isTableBody
class AsTableBody a where
_TableBody ::
Prism' a TableBody
instance AsTableBody TableBody where
_TableBody :: Prism' TableBody TableBody
_TableBody =
p TableBody (f TableBody) -> p TableBody (f TableBody)
forall a. a -> a
id
instance AsTableBody D.TableBody where
_TableBody :: Prism' TableBody TableBody
_TableBody =
AnIso TableBody TableBody TableBody TableBody
-> Iso TableBody TableBody TableBody TableBody
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso TableBody TableBody TableBody TableBody
Iso' TableBody TableBody
isTableBody
isTableBody ::
Iso'
TableBody
D.TableBody
isTableBody :: Iso' TableBody TableBody
isTableBody =
(TableBody -> TableBody)
-> (TableBody -> TableBody) -> Iso' TableBody TableBody
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(TableBody Attr
a RowHeadColumns
c [Row]
r1 [Row]
r2) -> Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
D.TableBody (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) (Getting RowHeadColumns RowHeadColumns RowHeadColumns
-> RowHeadColumns -> RowHeadColumns
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting RowHeadColumns RowHeadColumns RowHeadColumns
Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns RowHeadColumns
c) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Row Row Row -> Row -> Row
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Row Row Row
Iso' Row Row
isRow) [Row]
r1) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Row Row Row -> Row -> Row
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Row Row Row
Iso' Row Row
isRow) [Row]
r2))
(\(D.TableBody Attr
a RowHeadColumns
c [Row]
r1 [Row]
r2) -> Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) (AReview RowHeadColumns RowHeadColumns
-> RowHeadColumns -> RowHeadColumns
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview RowHeadColumns RowHeadColumns
Iso RowHeadColumns RowHeadColumns RowHeadColumns RowHeadColumns
isRowHeadColumns RowHeadColumns
c) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Row Row -> Row -> Row
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Row Row
Iso' Row Row
isRow) [Row]
r1) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Row Row -> Row -> Row
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Row Row
Iso' Row Row
isRow) [Row]
r2))
instance Walkable D.TableBody TableBody where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(TableBody -> m TableBody) -> TableBody -> m TableBody
walkM =
(TableBody -> m TableBody) -> TableBody -> m TableBody
Iso' TableBody TableBody
isTableBody
query :: forall c. Monoid c => (TableBody -> c) -> TableBody -> c
query TableBody -> c
f =
TableBody -> c
f (TableBody -> c) -> (TableBody -> TableBody) -> TableBody -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting TableBody TableBody TableBody -> TableBody -> TableBody
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting TableBody TableBody TableBody
Iso' TableBody TableBody
isTableBody
data =
Attr [Row]
deriving (TableFoot -> TableFoot -> Bool
(TableFoot -> TableFoot -> Bool)
-> (TableFoot -> TableFoot -> Bool) -> Eq TableFoot
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TableFoot -> TableFoot -> Bool
== :: TableFoot -> TableFoot -> Bool
$c/= :: TableFoot -> TableFoot -> Bool
/= :: TableFoot -> TableFoot -> Bool
Eq, Eq TableFoot
Eq TableFoot =>
(TableFoot -> TableFoot -> Ordering)
-> (TableFoot -> TableFoot -> Bool)
-> (TableFoot -> TableFoot -> Bool)
-> (TableFoot -> TableFoot -> Bool)
-> (TableFoot -> TableFoot -> Bool)
-> (TableFoot -> TableFoot -> TableFoot)
-> (TableFoot -> TableFoot -> TableFoot)
-> Ord TableFoot
TableFoot -> TableFoot -> Bool
TableFoot -> TableFoot -> Ordering
TableFoot -> TableFoot -> TableFoot
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 :: TableFoot -> TableFoot -> Ordering
compare :: TableFoot -> TableFoot -> Ordering
$c< :: TableFoot -> TableFoot -> Bool
< :: TableFoot -> TableFoot -> Bool
$c<= :: TableFoot -> TableFoot -> Bool
<= :: TableFoot -> TableFoot -> Bool
$c> :: TableFoot -> TableFoot -> Bool
> :: TableFoot -> TableFoot -> Bool
$c>= :: TableFoot -> TableFoot -> Bool
>= :: TableFoot -> TableFoot -> Bool
$cmax :: TableFoot -> TableFoot -> TableFoot
max :: TableFoot -> TableFoot -> TableFoot
$cmin :: TableFoot -> TableFoot -> TableFoot
min :: TableFoot -> TableFoot -> TableFoot
Ord, Int -> TableFoot -> ShowS
[TableFoot] -> ShowS
TableFoot -> String
(Int -> TableFoot -> ShowS)
-> (TableFoot -> String)
-> ([TableFoot] -> ShowS)
-> Show TableFoot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TableFoot -> ShowS
showsPrec :: Int -> TableFoot -> ShowS
$cshow :: TableFoot -> String
show :: TableFoot -> String
$cshowList :: [TableFoot] -> ShowS
showList :: [TableFoot] -> ShowS
Show, Typeable TableFoot
Typeable TableFoot =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableFoot -> c TableFoot)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableFoot)
-> (TableFoot -> Constr)
-> (TableFoot -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableFoot))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot))
-> ((forall b. Data b => b -> b) -> TableFoot -> TableFoot)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r)
-> (forall u. (forall d. Data d => d -> u) -> TableFoot -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TableFoot -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot)
-> Data TableFoot
TableFoot -> Constr
TableFoot -> DataType
(forall b. Data b => b -> b) -> TableFoot -> TableFoot
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) -> TableFoot -> u
forall u. (forall d. Data d => d -> u) -> TableFoot -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableFoot
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableFoot -> c TableFoot
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableFoot)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableFoot -> c TableFoot
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TableFoot -> c TableFoot
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableFoot
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TableFoot
$ctoConstr :: TableFoot -> Constr
toConstr :: TableFoot -> Constr
$cdataTypeOf :: TableFoot -> DataType
dataTypeOf :: TableFoot -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableFoot)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TableFoot)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot)
$cgmapT :: (forall b. Data b => b -> b) -> TableFoot -> TableFoot
gmapT :: (forall b. Data b => b -> b) -> TableFoot -> TableFoot
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TableFoot -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableFoot -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TableFoot -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableFoot -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableFoot -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TableFoot -> m TableFoot
Data, Typeable, ReadPrec [TableFoot]
ReadPrec TableFoot
Int -> ReadS TableFoot
ReadS [TableFoot]
(Int -> ReadS TableFoot)
-> ReadS [TableFoot]
-> ReadPrec TableFoot
-> ReadPrec [TableFoot]
-> Read TableFoot
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TableFoot
readsPrec :: Int -> ReadS TableFoot
$creadList :: ReadS [TableFoot]
readList :: ReadS [TableFoot]
$creadPrec :: ReadPrec TableFoot
readPrec :: ReadPrec TableFoot
$creadListPrec :: ReadPrec [TableFoot]
readListPrec :: ReadPrec [TableFoot]
Read, (forall x. TableFoot -> Rep TableFoot x)
-> (forall x. Rep TableFoot x -> TableFoot) -> Generic TableFoot
forall x. Rep TableFoot x -> TableFoot
forall x. TableFoot -> Rep TableFoot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TableFoot -> Rep TableFoot x
from :: forall x. TableFoot -> Rep TableFoot x
$cto :: forall x. Rep TableFoot x -> TableFoot
to :: forall x. Rep TableFoot x -> TableFoot
Generic)
instance Semigroup TableFoot where
TableFoot Attr
a1 [Row]
r1 <> :: TableFoot -> TableFoot -> TableFoot
<> TableFoot Attr
a2 [Row]
r2 =
Attr -> [Row] -> TableFoot
TableFoot (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) ([Row]
r1 [Row] -> [Row] -> [Row]
forall a. Semigroup a => a -> a -> a
<> [Row]
r2)
instance Monoid TableFoot where
mempty :: TableFoot
mempty =
Attr -> [Row] -> TableFoot
TableFoot Attr
forall a. Monoid a => a
mempty [Row]
forall a. Monoid a => a
mempty
class a where
::
Lens' a TableFoot
::
Lens' a [Row]
tableFootRows =
(TableFoot -> f TableFoot) -> a -> f a
forall a. HasTableFoot a => Lens' a TableFoot
Lens' a TableFoot
tableFoot ((TableFoot -> f TableFoot) -> a -> f a)
-> (([Row] -> f [Row]) -> TableFoot -> f TableFoot)
-> ([Row] -> f [Row])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Row] -> f [Row]) -> TableFoot -> f TableFoot
forall a. HasTableFoot a => Lens' a [Row]
Lens' TableFoot [Row]
tableFootRows
instance HasTableFoot TableFoot where
tableFoot :: Lens' TableFoot TableFoot
tableFoot =
(TableFoot -> f TableFoot) -> TableFoot -> f TableFoot
forall a. a -> a
id
tableFootRows :: Lens' TableFoot [Row]
tableFootRows [Row] -> f [Row]
f (TableFoot Attr
a [Row]
r) =
([Row] -> TableFoot) -> f [Row] -> f TableFoot
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Row] -> TableFoot
TableFoot Attr
a) ([Row] -> f [Row]
f [Row]
r)
instance HasAttr TableFoot where
attr :: Lens' TableFoot Attr
attr Attr -> f Attr
f (TableFoot Attr
a [Row]
r) =
(Attr -> TableFoot) -> f Attr -> f TableFoot
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Row] -> TableFoot
`TableFoot` [Row]
r) (Attr -> f Attr
f Attr
a)
instance HasTableFoot D.TableFoot where
tableFoot :: Lens' TableFoot TableFoot
tableFoot =
AnIso TableFoot TableFoot TableFoot TableFoot
-> Iso TableFoot TableFoot TableFoot TableFoot
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso TableFoot TableFoot TableFoot TableFoot
Iso' TableFoot TableFoot
isTableFoot
class a where
::
Prism' a TableFoot
instance AsTableFoot TableFoot where
_TableFoot :: Prism' TableFoot TableFoot
_TableFoot =
p TableFoot (f TableFoot) -> p TableFoot (f TableFoot)
forall a. a -> a
id
instance AsTableFoot D.TableFoot where
_TableFoot :: Prism' TableFoot TableFoot
_TableFoot =
AnIso TableFoot TableFoot TableFoot TableFoot
-> Iso TableFoot TableFoot TableFoot TableFoot
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso TableFoot TableFoot TableFoot TableFoot
Iso' TableFoot TableFoot
isTableFoot
isTableFoot ::
Iso'
TableFoot
D.TableFoot
=
(TableFoot -> TableFoot)
-> (TableFoot -> TableFoot) -> Iso' TableFoot TableFoot
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(TableFoot Attr
a [Row]
r) -> Attr -> [Row] -> TableFoot
D.TableFoot (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Row Row Row -> Row -> Row
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Row Row Row
Iso' Row Row
isRow) [Row]
r))
(\(D.TableFoot Attr
a [Row]
r) -> Attr -> [Row] -> TableFoot
TableFoot (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Row -> Row) -> [Row] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Row Row -> Row -> Row
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Row Row
Iso' Row Row
isRow) [Row]
r))
instance Walkable D.TableFoot TableFoot where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(TableFoot -> m TableFoot) -> TableFoot -> m TableFoot
walkM =
(TableFoot -> m TableFoot) -> TableFoot -> m TableFoot
Iso' TableFoot TableFoot
isTableFoot
query :: forall c. Monoid c => (TableFoot -> c) -> TableFoot -> c
query TableFoot -> c
f =
TableFoot -> c
f (TableFoot -> c) -> (TableFoot -> TableFoot) -> TableFoot -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting TableFoot TableFoot TableFoot -> TableFoot -> TableFoot
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting TableFoot TableFoot TableFoot
Iso' TableFoot TableFoot
isTableFoot
data Definition =
Definition
[Inline]
[[Block]]
deriving (Definition -> Definition -> Bool
(Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool) -> Eq Definition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Definition -> Definition -> Bool
== :: Definition -> Definition -> Bool
$c/= :: Definition -> Definition -> Bool
/= :: Definition -> Definition -> Bool
Eq, Eq Definition
Eq Definition =>
(Definition -> Definition -> Ordering)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Definition)
-> (Definition -> Definition -> Definition)
-> Ord Definition
Definition -> Definition -> Bool
Definition -> Definition -> Ordering
Definition -> Definition -> Definition
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 :: Definition -> Definition -> Ordering
compare :: Definition -> Definition -> Ordering
$c< :: Definition -> Definition -> Bool
< :: Definition -> Definition -> Bool
$c<= :: Definition -> Definition -> Bool
<= :: Definition -> Definition -> Bool
$c> :: Definition -> Definition -> Bool
> :: Definition -> Definition -> Bool
$c>= :: Definition -> Definition -> Bool
>= :: Definition -> Definition -> Bool
$cmax :: Definition -> Definition -> Definition
max :: Definition -> Definition -> Definition
$cmin :: Definition -> Definition -> Definition
min :: Definition -> Definition -> Definition
Ord, Int -> Definition -> ShowS
[Definition] -> ShowS
Definition -> String
(Int -> Definition -> ShowS)
-> (Definition -> String)
-> ([Definition] -> ShowS)
-> Show Definition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Definition -> ShowS
showsPrec :: Int -> Definition -> ShowS
$cshow :: Definition -> String
show :: Definition -> String
$cshowList :: [Definition] -> ShowS
showList :: [Definition] -> ShowS
Show, Typeable Definition
Typeable Definition =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Definition -> c Definition)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Definition)
-> (Definition -> Constr)
-> (Definition -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Definition))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Definition))
-> ((forall b. Data b => b -> b) -> Definition -> Definition)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r)
-> (forall u. (forall d. Data d => d -> u) -> Definition -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Definition -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition)
-> Data Definition
Definition -> Constr
Definition -> DataType
(forall b. Data b => b -> b) -> Definition -> Definition
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) -> Definition -> u
forall u. (forall d. Data d => d -> u) -> Definition -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Definition
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Definition -> c Definition
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Definition)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Definition)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Definition -> c Definition
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Definition -> c Definition
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Definition
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Definition
$ctoConstr :: Definition -> Constr
toConstr :: Definition -> Constr
$cdataTypeOf :: Definition -> DataType
dataTypeOf :: Definition -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Definition)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Definition)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Definition)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Definition)
$cgmapT :: (forall b. Data b => b -> b) -> Definition -> Definition
gmapT :: (forall b. Data b => b -> b) -> Definition -> Definition
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Definition -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Definition -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Definition -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Definition -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Definition -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Definition -> m Definition
Data, Typeable, ReadPrec [Definition]
ReadPrec Definition
Int -> ReadS Definition
ReadS [Definition]
(Int -> ReadS Definition)
-> ReadS [Definition]
-> ReadPrec Definition
-> ReadPrec [Definition]
-> Read Definition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Definition
readsPrec :: Int -> ReadS Definition
$creadList :: ReadS [Definition]
readList :: ReadS [Definition]
$creadPrec :: ReadPrec Definition
readPrec :: ReadPrec Definition
$creadListPrec :: ReadPrec [Definition]
readListPrec :: ReadPrec [Definition]
Read, (forall x. Definition -> Rep Definition x)
-> (forall x. Rep Definition x -> Definition) -> Generic Definition
forall x. Rep Definition x -> Definition
forall x. Definition -> Rep Definition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Definition -> Rep Definition x
from :: forall x. Definition -> Rep Definition x
$cto :: forall x. Rep Definition x -> Definition
to :: forall x. Rep Definition x -> Definition
Generic)
instance Semigroup Definition where
Definition [Inline]
i1 [[Block]]
b1 <> :: Definition -> Definition -> Definition
<> Definition [Inline]
i2 [[Block]]
b2 =
[Inline] -> [[Block]] -> Definition
Definition ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2) ([[Block]]
b1 [[Block]] -> [[Block]] -> [[Block]]
forall a. Semigroup a => a -> a -> a
<> [[Block]]
b2)
instance Monoid Definition where
mempty :: Definition
mempty =
[Inline] -> [[Block]] -> Definition
Definition [Inline]
forall a. Monoid a => a
mempty [[Block]]
forall a. Monoid a => a
mempty
class HasDefinition a where
definition ::
Lens' a Definition
definitionBlocks ::
Lens' a [[Block]]
definitionBlocks =
(Definition -> f Definition) -> a -> f a
forall a. HasDefinition a => Lens' a Definition
Lens' a Definition
definition ((Definition -> f Definition) -> a -> f a)
-> (([[Block]] -> f [[Block]]) -> Definition -> f Definition)
-> ([[Block]] -> f [[Block]])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Block]] -> f [[Block]]) -> Definition -> f Definition
forall a. HasDefinition a => Lens' a [[Block]]
Lens' Definition [[Block]]
definitionBlocks
instance HasDefinition Definition where
definition :: Lens' Definition Definition
definition =
(Definition -> f Definition) -> Definition -> f Definition
forall a. a -> a
id
definitionBlocks :: Lens' Definition [[Block]]
definitionBlocks [[Block]] -> f [[Block]]
f (Definition [Inline]
i [[Block]]
b) =
([[Block]] -> Definition) -> f [[Block]] -> f Definition
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Inline] -> [[Block]] -> Definition
Definition [Inline]
i) ([[Block]] -> f [[Block]]
f [[Block]]
b)
instance HasInlines Definition where
inlines :: Lens' Definition [Inline]
inlines [Inline] -> f [Inline]
f (Definition [Inline]
i [[Block]]
b) =
([Inline] -> Definition) -> f [Inline] -> f Definition
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Inline] -> [[Block]] -> Definition
`Definition` [[Block]]
b) ([Inline] -> f [Inline]
f [Inline]
i)
class AsDefinition a where
_Definition ::
Prism' a Definition
instance AsDefinition Definition where
_Definition :: Prism' Definition Definition
_Definition =
p Definition (f Definition) -> p Definition (f Definition)
forall a. a -> a
id
data =
Int
Attr
[Inline]
deriving (Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
/= :: Header -> Header -> Bool
Eq, Eq Header
Eq Header =>
(Header -> Header -> Ordering)
-> (Header -> Header -> Bool)
-> (Header -> Header -> Bool)
-> (Header -> Header -> Bool)
-> (Header -> Header -> Bool)
-> (Header -> Header -> Header)
-> (Header -> Header -> Header)
-> Ord Header
Header -> Header -> Bool
Header -> Header -> Ordering
Header -> Header -> Header
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 :: Header -> Header -> Ordering
compare :: Header -> Header -> Ordering
$c< :: Header -> Header -> Bool
< :: Header -> Header -> Bool
$c<= :: Header -> Header -> Bool
<= :: Header -> Header -> Bool
$c> :: Header -> Header -> Bool
> :: Header -> Header -> Bool
$c>= :: Header -> Header -> Bool
>= :: Header -> Header -> Bool
$cmax :: Header -> Header -> Header
max :: Header -> Header -> Header
$cmin :: Header -> Header -> Header
min :: Header -> Header -> Header
Ord, Int -> Header -> ShowS
[Header] -> ShowS
Header -> String
(Int -> Header -> ShowS)
-> (Header -> String) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Header -> ShowS
showsPrec :: Int -> Header -> ShowS
$cshow :: Header -> String
show :: Header -> String
$cshowList :: [Header] -> ShowS
showList :: [Header] -> ShowS
Show, Typeable Header
Typeable Header =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header)
-> (Header -> Constr)
-> (Header -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header))
-> ((forall b. Data b => b -> b) -> Header -> Header)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Header -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Header -> r)
-> (forall u. (forall d. Data d => d -> u) -> Header -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Header -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header)
-> Data Header
Header -> Constr
Header -> DataType
(forall b. Data b => b -> b) -> Header -> Header
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) -> Header -> u
forall u. (forall d. Data d => d -> u) -> Header -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Header -> c Header
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Header
$ctoConstr :: Header -> Constr
toConstr :: Header -> Constr
$cdataTypeOf :: Header -> DataType
dataTypeOf :: Header -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Header)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header)
$cgmapT :: (forall b. Data b => b -> b) -> Header -> Header
gmapT :: (forall b. Data b => b -> b) -> Header -> Header
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Header -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Header -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Header -> m Header
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Header -> m Header
Data, Typeable, ReadPrec [Header]
ReadPrec Header
Int -> ReadS Header
ReadS [Header]
(Int -> ReadS Header)
-> ReadS [Header]
-> ReadPrec Header
-> ReadPrec [Header]
-> Read Header
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Header
readsPrec :: Int -> ReadS Header
$creadList :: ReadS [Header]
readList :: ReadS [Header]
$creadPrec :: ReadPrec Header
readPrec :: ReadPrec Header
$creadListPrec :: ReadPrec [Header]
readListPrec :: ReadPrec [Header]
Read, (forall x. Header -> Rep Header x)
-> (forall x. Rep Header x -> Header) -> Generic Header
forall x. Rep Header x -> Header
forall x. Header -> Rep Header x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Header -> Rep Header x
from :: forall x. Header -> Rep Header x
$cto :: forall x. Rep Header x -> Header
to :: forall x. Rep Header x -> Header
Generic)
class a where
::
Lens' a Header
::
Lens' a Int
headerLevel =
(Header -> f Header) -> a -> f a
forall a. HasHeader a => Lens' a Header
Lens' a Header
header ((Header -> f Header) -> a -> f a)
-> ((Int -> f Int) -> Header -> f Header)
-> (Int -> f Int)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> f Int) -> Header -> f Header
forall a. HasHeader a => Lens' a Int
Lens' Header Int
headerLevel
instance HasHeader Header where
header :: Lens' Header Header
header =
(Header -> f Header) -> Header -> f Header
forall a. a -> a
id
headerLevel :: Lens' Header Int
headerLevel Int -> f Int
f (Header Int
l Attr
a [Inline]
i) =
(Int -> Header) -> f Int -> f Header
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
l' -> Int -> Attr -> [Inline] -> Header
Header Int
l' Attr
a [Inline]
i) (Int -> f Int
f Int
l)
instance HasAttr Header where
attr :: Lens' Header Attr
attr Attr -> f Attr
f (Header Int
l Attr
a [Inline]
i) =
(Attr -> Header) -> f Attr -> f Header
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Int -> Attr -> [Inline] -> Header
Header Int
l Attr
a' [Inline]
i) (Attr -> f Attr
f Attr
a)
instance HasInlines Header where
inlines :: Lens' Header [Inline]
inlines [Inline] -> f [Inline]
f (Header Int
l Attr
a [Inline]
i) =
([Inline] -> Header) -> f [Inline] -> f Header
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Attr -> [Inline] -> Header
Header Int
l Attr
a) ([Inline] -> f [Inline]
f [Inline]
i)
class a where
::
Prism' a Header
instance AsHeader Header where
_Header :: Prism' Header Header
_Header =
p Header (f Header) -> p Header (f Header)
forall a. a -> a
id
instance AsHeader Block where
_Header :: Prism' Block Header
_Header =
(Header -> Block) -> (Block -> Maybe Header) -> Prism' Block Header
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Header -> Block
HeaderBlock
(\case
HeaderBlock Header
x -> Header -> Maybe Header
forall a. a -> Maybe a
Just Header
x
Block
_ -> Maybe Header
forall a. Maybe a
Nothing)
instance AsHeader D.Block where
_Header :: Prism' Block Header
_Header =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p Header (f Header) -> p Block (f Block))
-> p Header (f Header)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Header (f Header) -> p Block (f Block)
forall a. AsHeader a => Prism' a Header
Prism' Block Header
_Header
data OrderedList =
OrderedList
ListAttributes
[[Block]]
deriving (OrderedList -> OrderedList -> Bool
(OrderedList -> OrderedList -> Bool)
-> (OrderedList -> OrderedList -> Bool) -> Eq OrderedList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OrderedList -> OrderedList -> Bool
== :: OrderedList -> OrderedList -> Bool
$c/= :: OrderedList -> OrderedList -> Bool
/= :: OrderedList -> OrderedList -> Bool
Eq, Eq OrderedList
Eq OrderedList =>
(OrderedList -> OrderedList -> Ordering)
-> (OrderedList -> OrderedList -> Bool)
-> (OrderedList -> OrderedList -> Bool)
-> (OrderedList -> OrderedList -> Bool)
-> (OrderedList -> OrderedList -> Bool)
-> (OrderedList -> OrderedList -> OrderedList)
-> (OrderedList -> OrderedList -> OrderedList)
-> Ord OrderedList
OrderedList -> OrderedList -> Bool
OrderedList -> OrderedList -> Ordering
OrderedList -> OrderedList -> OrderedList
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 :: OrderedList -> OrderedList -> Ordering
compare :: OrderedList -> OrderedList -> Ordering
$c< :: OrderedList -> OrderedList -> Bool
< :: OrderedList -> OrderedList -> Bool
$c<= :: OrderedList -> OrderedList -> Bool
<= :: OrderedList -> OrderedList -> Bool
$c> :: OrderedList -> OrderedList -> Bool
> :: OrderedList -> OrderedList -> Bool
$c>= :: OrderedList -> OrderedList -> Bool
>= :: OrderedList -> OrderedList -> Bool
$cmax :: OrderedList -> OrderedList -> OrderedList
max :: OrderedList -> OrderedList -> OrderedList
$cmin :: OrderedList -> OrderedList -> OrderedList
min :: OrderedList -> OrderedList -> OrderedList
Ord, Int -> OrderedList -> ShowS
[OrderedList] -> ShowS
OrderedList -> String
(Int -> OrderedList -> ShowS)
-> (OrderedList -> String)
-> ([OrderedList] -> ShowS)
-> Show OrderedList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OrderedList -> ShowS
showsPrec :: Int -> OrderedList -> ShowS
$cshow :: OrderedList -> String
show :: OrderedList -> String
$cshowList :: [OrderedList] -> ShowS
showList :: [OrderedList] -> ShowS
Show, Typeable OrderedList
Typeable OrderedList =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedList -> c OrderedList)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedList)
-> (OrderedList -> Constr)
-> (OrderedList -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedList))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedList))
-> ((forall b. Data b => b -> b) -> OrderedList -> OrderedList)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r)
-> (forall u. (forall d. Data d => d -> u) -> OrderedList -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> OrderedList -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList)
-> Data OrderedList
OrderedList -> Constr
OrderedList -> DataType
(forall b. Data b => b -> b) -> OrderedList -> OrderedList
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) -> OrderedList -> u
forall u. (forall d. Data d => d -> u) -> OrderedList -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedList
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedList -> c OrderedList
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedList)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedList)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedList -> c OrderedList
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> OrderedList -> c OrderedList
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedList
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c OrderedList
$ctoConstr :: OrderedList -> Constr
toConstr :: OrderedList -> Constr
$cdataTypeOf :: OrderedList -> DataType
dataTypeOf :: OrderedList -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedList)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c OrderedList)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedList)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c OrderedList)
$cgmapT :: (forall b. Data b => b -> b) -> OrderedList -> OrderedList
gmapT :: (forall b. Data b => b -> b) -> OrderedList -> OrderedList
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> OrderedList -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> OrderedList -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> OrderedList -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OrderedList -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> OrderedList -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> OrderedList -> m OrderedList
Data, Typeable, ReadPrec [OrderedList]
ReadPrec OrderedList
Int -> ReadS OrderedList
ReadS [OrderedList]
(Int -> ReadS OrderedList)
-> ReadS [OrderedList]
-> ReadPrec OrderedList
-> ReadPrec [OrderedList]
-> Read OrderedList
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OrderedList
readsPrec :: Int -> ReadS OrderedList
$creadList :: ReadS [OrderedList]
readList :: ReadS [OrderedList]
$creadPrec :: ReadPrec OrderedList
readPrec :: ReadPrec OrderedList
$creadListPrec :: ReadPrec [OrderedList]
readListPrec :: ReadPrec [OrderedList]
Read, (forall x. OrderedList -> Rep OrderedList x)
-> (forall x. Rep OrderedList x -> OrderedList)
-> Generic OrderedList
forall x. Rep OrderedList x -> OrderedList
forall x. OrderedList -> Rep OrderedList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OrderedList -> Rep OrderedList x
from :: forall x. OrderedList -> Rep OrderedList x
$cto :: forall x. Rep OrderedList x -> OrderedList
to :: forall x. Rep OrderedList x -> OrderedList
Generic)
instance Semigroup OrderedList where
OrderedList ListAttributes
a1 [[Block]]
b1 <> :: OrderedList -> OrderedList -> OrderedList
<> OrderedList ListAttributes
a2 [[Block]]
b2 =
ListAttributes -> [[Block]] -> OrderedList
OrderedList (ListAttributes
a1 ListAttributes -> ListAttributes -> ListAttributes
forall a. Semigroup a => a -> a -> a
<> ListAttributes
a2) ([[Block]]
b1 [[Block]] -> [[Block]] -> [[Block]]
forall a. Semigroup a => a -> a -> a
<> [[Block]]
b2)
instance Monoid OrderedList where
mempty :: OrderedList
mempty =
ListAttributes -> [[Block]] -> OrderedList
OrderedList ListAttributes
forall a. Monoid a => a
mempty [[Block]]
forall a. Monoid a => a
mempty
class HasOrderedList a where
orderedList ::
Lens' a OrderedList
orderedListBlocks ::
Lens' a [[Block]]
orderedListBlocks =
(OrderedList -> f OrderedList) -> a -> f a
forall a. HasOrderedList a => Lens' a OrderedList
Lens' a OrderedList
orderedList ((OrderedList -> f OrderedList) -> a -> f a)
-> (([[Block]] -> f [[Block]]) -> OrderedList -> f OrderedList)
-> ([[Block]] -> f [[Block]])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Block]] -> f [[Block]]) -> OrderedList -> f OrderedList
forall a. HasOrderedList a => Lens' a [[Block]]
Lens' OrderedList [[Block]]
orderedListBlocks
instance HasOrderedList OrderedList where
orderedList :: Lens' OrderedList OrderedList
orderedList =
(OrderedList -> f OrderedList) -> OrderedList -> f OrderedList
forall a. a -> a
id
orderedListBlocks :: Lens' OrderedList [[Block]]
orderedListBlocks [[Block]] -> f [[Block]]
f (OrderedList ListAttributes
a [[Block]]
b) =
([[Block]] -> OrderedList) -> f [[Block]] -> f OrderedList
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ListAttributes -> [[Block]] -> OrderedList
OrderedList ListAttributes
a) ([[Block]] -> f [[Block]]
f [[Block]]
b)
instance HasListAttributes OrderedList where
listAttributes :: Lens' OrderedList ListAttributes
listAttributes ListAttributes -> f ListAttributes
f (OrderedList ListAttributes
a [[Block]]
b) =
(ListAttributes -> OrderedList)
-> f ListAttributes -> f OrderedList
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ListAttributes -> [[Block]] -> OrderedList
`OrderedList` [[Block]]
b) (ListAttributes -> f ListAttributes
f ListAttributes
a)
class AsOrderedList a where
_OrderedList ::
Prism' a OrderedList
instance AsOrderedList OrderedList where
_OrderedList :: Prism' OrderedList OrderedList
_OrderedList =
p OrderedList (f OrderedList) -> p OrderedList (f OrderedList)
forall a. a -> a
id
instance AsOrderedList Block where
_OrderedList :: Prism' Block OrderedList
_OrderedList =
(OrderedList -> Block)
-> (Block -> Maybe OrderedList) -> Prism' Block OrderedList
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
OrderedList -> Block
OrderedListBlock
(\case
OrderedListBlock OrderedList
x -> OrderedList -> Maybe OrderedList
forall a. a -> Maybe a
Just OrderedList
x
Block
_ -> Maybe OrderedList
forall a. Maybe a
Nothing)
instance AsOrderedList D.Block where
_OrderedList :: Prism' Block OrderedList
_OrderedList =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p OrderedList (f OrderedList) -> p Block (f Block))
-> p OrderedList (f OrderedList)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p OrderedList (f OrderedList) -> p Block (f Block)
forall a. AsOrderedList a => Prism' a OrderedList
Prism' Block OrderedList
_OrderedList
data Code =
Code
Attr
Text
deriving (Code -> Code -> Bool
(Code -> Code -> Bool) -> (Code -> Code -> Bool) -> Eq Code
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Code -> Code -> Bool
== :: Code -> Code -> Bool
$c/= :: Code -> Code -> Bool
/= :: Code -> Code -> Bool
Eq, Eq Code
Eq Code =>
(Code -> Code -> Ordering)
-> (Code -> Code -> Bool)
-> (Code -> Code -> Bool)
-> (Code -> Code -> Bool)
-> (Code -> Code -> Bool)
-> (Code -> Code -> Code)
-> (Code -> Code -> Code)
-> Ord Code
Code -> Code -> Bool
Code -> Code -> Ordering
Code -> Code -> Code
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 :: Code -> Code -> Ordering
compare :: Code -> Code -> Ordering
$c< :: Code -> Code -> Bool
< :: Code -> Code -> Bool
$c<= :: Code -> Code -> Bool
<= :: Code -> Code -> Bool
$c> :: Code -> Code -> Bool
> :: Code -> Code -> Bool
$c>= :: Code -> Code -> Bool
>= :: Code -> Code -> Bool
$cmax :: Code -> Code -> Code
max :: Code -> Code -> Code
$cmin :: Code -> Code -> Code
min :: Code -> Code -> Code
Ord, Int -> Code -> ShowS
[Code] -> ShowS
Code -> String
(Int -> Code -> ShowS)
-> (Code -> String) -> ([Code] -> ShowS) -> Show Code
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Code -> ShowS
showsPrec :: Int -> Code -> ShowS
$cshow :: Code -> String
show :: Code -> String
$cshowList :: [Code] -> ShowS
showList :: [Code] -> ShowS
Show, Typeable Code
Typeable Code =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Code -> c Code)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Code)
-> (Code -> Constr)
-> (Code -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Code))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Code))
-> ((forall b. Data b => b -> b) -> Code -> Code)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r)
-> (forall u. (forall d. Data d => d -> u) -> Code -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Code -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Code -> m Code)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code)
-> Data Code
Code -> Constr
Code -> DataType
(forall b. Data b => b -> b) -> Code -> Code
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) -> Code -> u
forall u. (forall d. Data d => d -> u) -> Code -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Code -> m Code
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Code
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Code -> c Code
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Code)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Code)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Code -> c Code
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Code -> c Code
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Code
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Code
$ctoConstr :: Code -> Constr
toConstr :: Code -> Constr
$cdataTypeOf :: Code -> DataType
dataTypeOf :: Code -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Code)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Code)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Code)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Code)
$cgmapT :: (forall b. Data b => b -> b) -> Code -> Code
gmapT :: (forall b. Data b => b -> b) -> Code -> Code
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Code -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Code -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Code -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Code -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Code -> m Code
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Code -> m Code
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Code -> m Code
Data, Typeable, ReadPrec [Code]
ReadPrec Code
Int -> ReadS Code
ReadS [Code]
(Int -> ReadS Code)
-> ReadS [Code] -> ReadPrec Code -> ReadPrec [Code] -> Read Code
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Code
readsPrec :: Int -> ReadS Code
$creadList :: ReadS [Code]
readList :: ReadS [Code]
$creadPrec :: ReadPrec Code
readPrec :: ReadPrec Code
$creadListPrec :: ReadPrec [Code]
readListPrec :: ReadPrec [Code]
Read, (forall x. Code -> Rep Code x)
-> (forall x. Rep Code x -> Code) -> Generic Code
forall x. Rep Code x -> Code
forall x. Code -> Rep Code x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Code -> Rep Code x
from :: forall x. Code -> Rep Code x
$cto :: forall x. Rep Code x -> Code
to :: forall x. Rep Code x -> Code
Generic)
instance Semigroup Code where
Code Attr
a1 Text
t1 <> :: Code -> Code -> Code
<> Code Attr
a2 Text
t2 =
Attr -> Text -> Code
Code (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) (Text
t1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t2)
instance Monoid Code where
mempty :: Code
mempty =
Attr -> Text -> Code
Code Attr
forall a. Monoid a => a
mempty Text
forall a. Monoid a => a
mempty
class HasCode a where
code ::
Lens' a Code
instance HasCode Code where
code :: Lens' Code Code
code =
(Code -> f Code) -> Code -> f Code
forall a. a -> a
id
instance HasAttr Code where
attr :: Lens' Code Attr
attr Attr -> f Attr
f (Code Attr
a Text
t) =
(Attr -> Code) -> f Attr -> f Code
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Text -> Code
`Code` Text
t) (Attr -> f Attr
f Attr
a)
instance HasText Code where
text :: Lens' Code Text
text Text -> f Text
f (Code Attr
a Text
t) =
(Text -> Code) -> f Text -> f Code
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Text -> Code
Code Attr
a) (Text -> f Text
f Text
t)
class AsCode a where
_Code ::
Prism' a Code
instance AsCode Code where
_Code :: Prism' Code Code
_Code =
p Code (f Code) -> p Code (f Code)
forall a. a -> a
id
instance AsCode Block where
_Code :: Prism' Block Code
_Code =
(Code -> Block) -> (Block -> Maybe Code) -> Prism' Block Code
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Code -> Block
CodeBlock
(\case
CodeBlock Code
x -> Code -> Maybe Code
forall a. a -> Maybe a
Just Code
x
Block
_ -> Maybe Code
forall a. Maybe a
Nothing)
instance AsCode D.Block where
_Code :: Prism' Block Code
_Code =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p Code (f Code) -> p Block (f Block))
-> p Code (f Code)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Code (f Code) -> p Block (f Block)
forall a. AsCode a => Prism' a Code
Prism' Block Code
_Code
data Raw =
Raw
Format
Text
deriving (Raw -> Raw -> Bool
(Raw -> Raw -> Bool) -> (Raw -> Raw -> Bool) -> Eq Raw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Raw -> Raw -> Bool
== :: Raw -> Raw -> Bool
$c/= :: Raw -> Raw -> Bool
/= :: Raw -> Raw -> Bool
Eq, Eq Raw
Eq Raw =>
(Raw -> Raw -> Ordering)
-> (Raw -> Raw -> Bool)
-> (Raw -> Raw -> Bool)
-> (Raw -> Raw -> Bool)
-> (Raw -> Raw -> Bool)
-> (Raw -> Raw -> Raw)
-> (Raw -> Raw -> Raw)
-> Ord Raw
Raw -> Raw -> Bool
Raw -> Raw -> Ordering
Raw -> Raw -> Raw
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 :: Raw -> Raw -> Ordering
compare :: Raw -> Raw -> Ordering
$c< :: Raw -> Raw -> Bool
< :: Raw -> Raw -> Bool
$c<= :: Raw -> Raw -> Bool
<= :: Raw -> Raw -> Bool
$c> :: Raw -> Raw -> Bool
> :: Raw -> Raw -> Bool
$c>= :: Raw -> Raw -> Bool
>= :: Raw -> Raw -> Bool
$cmax :: Raw -> Raw -> Raw
max :: Raw -> Raw -> Raw
$cmin :: Raw -> Raw -> Raw
min :: Raw -> Raw -> Raw
Ord, Int -> Raw -> ShowS
[Raw] -> ShowS
Raw -> String
(Int -> Raw -> ShowS)
-> (Raw -> String) -> ([Raw] -> ShowS) -> Show Raw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Raw -> ShowS
showsPrec :: Int -> Raw -> ShowS
$cshow :: Raw -> String
show :: Raw -> String
$cshowList :: [Raw] -> ShowS
showList :: [Raw] -> ShowS
Show, Typeable Raw
Typeable Raw =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Raw -> c Raw)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Raw)
-> (Raw -> Constr)
-> (Raw -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Raw))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Raw))
-> ((forall b. Data b => b -> b) -> Raw -> Raw)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r)
-> (forall u. (forall d. Data d => d -> u) -> Raw -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Raw -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw)
-> Data Raw
Raw -> Constr
Raw -> DataType
(forall b. Data b => b -> b) -> Raw -> Raw
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) -> Raw -> u
forall u. (forall d. Data d => d -> u) -> Raw -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Raw
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Raw -> c Raw
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Raw)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Raw)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Raw -> c Raw
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Raw -> c Raw
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Raw
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Raw
$ctoConstr :: Raw -> Constr
toConstr :: Raw -> Constr
$cdataTypeOf :: Raw -> DataType
dataTypeOf :: Raw -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Raw)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Raw)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Raw)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Raw)
$cgmapT :: (forall b. Data b => b -> b) -> Raw -> Raw
gmapT :: (forall b. Data b => b -> b) -> Raw -> Raw
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Raw -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Raw -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Raw -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Raw -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Raw -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Raw -> m Raw
Data, Typeable, ReadPrec [Raw]
ReadPrec Raw
Int -> ReadS Raw
ReadS [Raw]
(Int -> ReadS Raw)
-> ReadS [Raw] -> ReadPrec Raw -> ReadPrec [Raw] -> Read Raw
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Raw
readsPrec :: Int -> ReadS Raw
$creadList :: ReadS [Raw]
readList :: ReadS [Raw]
$creadPrec :: ReadPrec Raw
readPrec :: ReadPrec Raw
$creadListPrec :: ReadPrec [Raw]
readListPrec :: ReadPrec [Raw]
Read, (forall x. Raw -> Rep Raw x)
-> (forall x. Rep Raw x -> Raw) -> Generic Raw
forall x. Rep Raw x -> Raw
forall x. Raw -> Rep Raw x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Raw -> Rep Raw x
from :: forall x. Raw -> Rep Raw x
$cto :: forall x. Rep Raw x -> Raw
to :: forall x. Rep Raw x -> Raw
Generic)
class HasRaw a where
raw ::
Lens' a Raw
instance HasRaw Raw where
raw :: Lens' Raw Raw
raw =
(Raw -> f Raw) -> Raw -> f Raw
forall a. a -> a
id
instance HasText Raw where
text :: Lens' Raw Text
text Text -> f Text
f (Raw Format
r Text
t) =
(Text -> Raw) -> f Text -> f Raw
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Format -> Text -> Raw
Raw Format
r) (Text -> f Text
f Text
t)
class AsRaw a where
_Raw ::
Prism' a Raw
instance AsRaw Raw where
_Raw :: Prism' Raw Raw
_Raw =
p Raw (f Raw) -> p Raw (f Raw)
forall a. a -> a
id
instance AsRaw Block where
_Raw :: Prism' Block Raw
_Raw =
(Raw -> Block) -> (Block -> Maybe Raw) -> Prism' Block Raw
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Raw -> Block
RawBlock
(\case
RawBlock Raw
i -> Raw -> Maybe Raw
forall a. a -> Maybe a
Just Raw
i
Block
_ -> Maybe Raw
forall a. Maybe a
Nothing)
instance AsRaw D.Block where
_Raw :: Prism' Block Raw
_Raw =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p Raw (f Raw) -> p Block (f Block))
-> p Raw (f Raw)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Raw (f Raw) -> p Block (f Block)
forall a. AsRaw a => Prism' a Raw
Prism' Block Raw
_Raw
data Table =
Table
Attr
Caption
[ColSpec]
TableHead
[TableBody]
TableFoot
deriving (Table -> Table -> Bool
(Table -> Table -> Bool) -> (Table -> Table -> Bool) -> Eq Table
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Table -> Table -> Bool
== :: Table -> Table -> Bool
$c/= :: Table -> Table -> Bool
/= :: Table -> Table -> Bool
Eq, Eq Table
Eq Table =>
(Table -> Table -> Ordering)
-> (Table -> Table -> Bool)
-> (Table -> Table -> Bool)
-> (Table -> Table -> Bool)
-> (Table -> Table -> Bool)
-> (Table -> Table -> Table)
-> (Table -> Table -> Table)
-> Ord Table
Table -> Table -> Bool
Table -> Table -> Ordering
Table -> Table -> Table
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 :: Table -> Table -> Ordering
compare :: Table -> Table -> Ordering
$c< :: Table -> Table -> Bool
< :: Table -> Table -> Bool
$c<= :: Table -> Table -> Bool
<= :: Table -> Table -> Bool
$c> :: Table -> Table -> Bool
> :: Table -> Table -> Bool
$c>= :: Table -> Table -> Bool
>= :: Table -> Table -> Bool
$cmax :: Table -> Table -> Table
max :: Table -> Table -> Table
$cmin :: Table -> Table -> Table
min :: Table -> Table -> Table
Ord, Int -> Table -> ShowS
[Table] -> ShowS
Table -> String
(Int -> Table -> ShowS)
-> (Table -> String) -> ([Table] -> ShowS) -> Show Table
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Table -> ShowS
showsPrec :: Int -> Table -> ShowS
$cshow :: Table -> String
show :: Table -> String
$cshowList :: [Table] -> ShowS
showList :: [Table] -> ShowS
Show, Typeable Table
Typeable Table =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Table -> c Table)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Table)
-> (Table -> Constr)
-> (Table -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Table))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table))
-> ((forall b. Data b => b -> b) -> Table -> Table)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r)
-> (forall u. (forall d. Data d => d -> u) -> Table -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Table -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Table -> m Table)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table)
-> Data Table
Table -> Constr
Table -> DataType
(forall b. Data b => b -> b) -> Table -> Table
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) -> Table -> u
forall u. (forall d. Data d => d -> u) -> Table -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Table -> m Table
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Table
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Table -> c Table
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Table)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Table -> c Table
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Table -> c Table
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Table
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Table
$ctoConstr :: Table -> Constr
toConstr :: Table -> Constr
$cdataTypeOf :: Table -> DataType
dataTypeOf :: Table -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Table)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Table)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table)
$cgmapT :: (forall b. Data b => b -> b) -> Table -> Table
gmapT :: (forall b. Data b => b -> b) -> Table -> Table
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Table -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Table -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Table -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Table -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Table -> m Table
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Table -> m Table
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Table -> m Table
Data, Typeable, ReadPrec [Table]
ReadPrec Table
Int -> ReadS Table
ReadS [Table]
(Int -> ReadS Table)
-> ReadS [Table]
-> ReadPrec Table
-> ReadPrec [Table]
-> Read Table
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Table
readsPrec :: Int -> ReadS Table
$creadList :: ReadS [Table]
readList :: ReadS [Table]
$creadPrec :: ReadPrec Table
readPrec :: ReadPrec Table
$creadListPrec :: ReadPrec [Table]
readListPrec :: ReadPrec [Table]
Read, (forall x. Table -> Rep Table x)
-> (forall x. Rep Table x -> Table) -> Generic Table
forall x. Rep Table x -> Table
forall x. Table -> Rep Table x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Table -> Rep Table x
from :: forall x. Table -> Rep Table x
$cto :: forall x. Rep Table x -> Table
to :: forall x. Rep Table x -> Table
Generic)
instance Semigroup Table where
Table Attr
a1 Caption
c1 [ColSpec]
s1 TableHead
h1 [TableBody]
b1 TableFoot
t1 <> :: Table -> Table -> Table
<> Table Attr
a2 Caption
c2 [ColSpec]
s2 TableHead
h2 [TableBody]
b2 TableFoot
t2 =
Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) (Caption
c1 Caption -> Caption -> Caption
forall a. Semigroup a => a -> a -> a
<> Caption
c2) ([ColSpec]
s1 [ColSpec] -> [ColSpec] -> [ColSpec]
forall a. Semigroup a => a -> a -> a
<> [ColSpec]
s2) (TableHead
h1 TableHead -> TableHead -> TableHead
forall a. Semigroup a => a -> a -> a
<> TableHead
h2) ([TableBody]
b1 [TableBody] -> [TableBody] -> [TableBody]
forall a. Semigroup a => a -> a -> a
<> [TableBody]
b2) (TableFoot
t1 TableFoot -> TableFoot -> TableFoot
forall a. Semigroup a => a -> a -> a
<> TableFoot
t2)
instance Monoid Table where
mempty :: Table
mempty =
Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
forall a. Monoid a => a
mempty Caption
forall a. Monoid a => a
mempty [ColSpec]
forall a. Monoid a => a
mempty TableHead
forall a. Monoid a => a
mempty [TableBody]
forall a. Monoid a => a
mempty TableFoot
forall a. Monoid a => a
mempty
class HasTable a where
table ::
Lens' a Table
tableColSpecs ::
Lens' a [ColSpec]
tableColSpecs =
(Table -> f Table) -> a -> f a
forall a. HasTable a => Lens' a Table
Lens' a Table
table ((Table -> f Table) -> a -> f a)
-> (([ColSpec] -> f [ColSpec]) -> Table -> f Table)
-> ([ColSpec] -> f [ColSpec])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([ColSpec] -> f [ColSpec]) -> Table -> f Table
forall a. HasTable a => Lens' a [ColSpec]
Lens' Table [ColSpec]
tableColSpecs
tableBodies ::
Lens' a [TableBody]
tableBodies =
(Table -> f Table) -> a -> f a
forall a. HasTable a => Lens' a Table
Lens' a Table
table ((Table -> f Table) -> a -> f a)
-> (([TableBody] -> f [TableBody]) -> Table -> f Table)
-> ([TableBody] -> f [TableBody])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([TableBody] -> f [TableBody]) -> Table -> f Table
forall a. HasTable a => Lens' a [TableBody]
Lens' Table [TableBody]
tableBodies
instance HasTable Table where
table :: Lens' Table Table
table =
(Table -> f Table) -> Table -> f Table
forall a. a -> a
id
tableColSpecs :: Lens' Table [ColSpec]
tableColSpecs [ColSpec] -> f [ColSpec]
f (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) =
([ColSpec] -> Table) -> f [ColSpec] -> f Table
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[ColSpec]
s' -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
a Caption
c [ColSpec]
s' TableHead
h [TableBody]
b TableFoot
t) ([ColSpec] -> f [ColSpec]
f [ColSpec]
s)
tableBodies :: Lens' Table [TableBody]
tableBodies [TableBody] -> f [TableBody]
f (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) =
([TableBody] -> Table) -> f [TableBody] -> f Table
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[TableBody]
b' -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b' TableFoot
t) ([TableBody] -> f [TableBody]
f [TableBody]
b)
instance HasAttr Table where
attr :: Lens' Table Attr
attr Attr -> f Attr
f (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) =
(Attr -> Table) -> f Attr -> f Table
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
a' Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) (Attr -> f Attr
f Attr
a)
instance HasCaption Table where
caption :: Lens' Table Caption
caption Caption -> f Caption
f (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) =
(Caption -> Table) -> f Caption -> f Table
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Caption
c' -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
a Caption
c' [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) (Caption -> f Caption
f Caption
c)
instance HasTableHead Table where
tableHead :: Lens' Table TableHead
tableHead TableHead -> f TableHead
f (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) =
(TableHead -> Table) -> f TableHead -> f Table
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\TableHead
h' -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
a Caption
c [ColSpec]
s TableHead
h' [TableBody]
b TableFoot
t) (TableHead -> f TableHead
f TableHead
h)
instance HasTableFoot Table where
tableFoot :: Lens' Table TableFoot
tableFoot TableFoot -> f TableFoot
f (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
t) =
(TableFoot -> Table) -> f TableFoot -> f Table
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b) (TableFoot -> f TableFoot
f TableFoot
t)
class AsTable a where
_Table ::
Prism' a Table
instance AsTable Table where
_Table :: Prism' Table Table
_Table =
p Table (f Table) -> p Table (f Table)
forall a. a -> a
id
instance AsTable Block where
_Table :: Prism' Block Table
_Table =
(Table -> Block) -> (Block -> Maybe Table) -> Prism' Block Table
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Table -> Block
TableBlock
(\case
TableBlock Table
i -> Table -> Maybe Table
forall a. a -> Maybe a
Just Table
i
Block
_ -> Maybe Table
forall a. Maybe a
Nothing)
instance AsTable D.Block where
_Table :: Prism' Block Table
_Table =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p Table (f Table) -> p Block (f Block))
-> p Table (f Table)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Table (f Table) -> p Block (f Block)
forall a. AsTable a => Prism' a Table
Prism' Block Table
_Table
data Figure =
Figure
Attr
Caption
[Block]
deriving (Figure -> Figure -> Bool
(Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool) -> Eq Figure
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Figure -> Figure -> Bool
== :: Figure -> Figure -> Bool
$c/= :: Figure -> Figure -> Bool
/= :: Figure -> Figure -> Bool
Eq, Eq Figure
Eq Figure =>
(Figure -> Figure -> Ordering)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Bool)
-> (Figure -> Figure -> Figure)
-> (Figure -> Figure -> Figure)
-> Ord Figure
Figure -> Figure -> Bool
Figure -> Figure -> Ordering
Figure -> Figure -> Figure
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 :: Figure -> Figure -> Ordering
compare :: Figure -> Figure -> Ordering
$c< :: Figure -> Figure -> Bool
< :: Figure -> Figure -> Bool
$c<= :: Figure -> Figure -> Bool
<= :: Figure -> Figure -> Bool
$c> :: Figure -> Figure -> Bool
> :: Figure -> Figure -> Bool
$c>= :: Figure -> Figure -> Bool
>= :: Figure -> Figure -> Bool
$cmax :: Figure -> Figure -> Figure
max :: Figure -> Figure -> Figure
$cmin :: Figure -> Figure -> Figure
min :: Figure -> Figure -> Figure
Ord, Int -> Figure -> ShowS
[Figure] -> ShowS
Figure -> String
(Int -> Figure -> ShowS)
-> (Figure -> String) -> ([Figure] -> ShowS) -> Show Figure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Figure -> ShowS
showsPrec :: Int -> Figure -> ShowS
$cshow :: Figure -> String
show :: Figure -> String
$cshowList :: [Figure] -> ShowS
showList :: [Figure] -> ShowS
Show, Typeable Figure
Typeable Figure =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Figure -> c Figure)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Figure)
-> (Figure -> Constr)
-> (Figure -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Figure))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Figure))
-> ((forall b. Data b => b -> b) -> Figure -> Figure)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Figure -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Figure -> r)
-> (forall u. (forall d. Data d => d -> u) -> Figure -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Figure -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure)
-> Data Figure
Figure -> Constr
Figure -> DataType
(forall b. Data b => b -> b) -> Figure -> Figure
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) -> Figure -> u
forall u. (forall d. Data d => d -> u) -> Figure -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Figure -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Figure -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Figure
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Figure -> c Figure
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Figure)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Figure)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Figure -> c Figure
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Figure -> c Figure
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Figure
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Figure
$ctoConstr :: Figure -> Constr
toConstr :: Figure -> Constr
$cdataTypeOf :: Figure -> DataType
dataTypeOf :: Figure -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Figure)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Figure)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Figure)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Figure)
$cgmapT :: (forall b. Data b => b -> b) -> Figure -> Figure
gmapT :: (forall b. Data b => b -> b) -> Figure -> Figure
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Figure -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Figure -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Figure -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Figure -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Figure -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Figure -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Figure -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Figure -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Figure -> m Figure
Data, Typeable, ReadPrec [Figure]
ReadPrec Figure
Int -> ReadS Figure
ReadS [Figure]
(Int -> ReadS Figure)
-> ReadS [Figure]
-> ReadPrec Figure
-> ReadPrec [Figure]
-> Read Figure
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Figure
readsPrec :: Int -> ReadS Figure
$creadList :: ReadS [Figure]
readList :: ReadS [Figure]
$creadPrec :: ReadPrec Figure
readPrec :: ReadPrec Figure
$creadListPrec :: ReadPrec [Figure]
readListPrec :: ReadPrec [Figure]
Read, (forall x. Figure -> Rep Figure x)
-> (forall x. Rep Figure x -> Figure) -> Generic Figure
forall x. Rep Figure x -> Figure
forall x. Figure -> Rep Figure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Figure -> Rep Figure x
from :: forall x. Figure -> Rep Figure x
$cto :: forall x. Rep Figure x -> Figure
to :: forall x. Rep Figure x -> Figure
Generic)
instance Semigroup Figure where
Figure Attr
a1 Caption
c1 [Block]
b1 <> :: Figure -> Figure -> Figure
<> Figure Attr
a2 Caption
c2 [Block]
b2 =
Attr -> Caption -> [Block] -> Figure
Figure (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) (Caption
c1 Caption -> Caption -> Caption
forall a. Semigroup a => a -> a -> a
<> Caption
c2) ([Block]
b1 [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
b2)
instance Monoid Figure where
mempty :: Figure
mempty =
Attr -> Caption -> [Block] -> Figure
Figure Attr
forall a. Monoid a => a
mempty Caption
forall a. Monoid a => a
mempty [Block]
forall a. Monoid a => a
mempty
class HasFigure a where
figure ::
Lens' a Figure
instance HasFigure Figure where
figure :: Lens' Figure Figure
figure =
(Figure -> f Figure) -> Figure -> f Figure
forall a. a -> a
id
instance HasBlocks Figure where
blocks :: Lens' Figure [Block]
blocks [Block] -> f [Block]
f (Figure Attr
a Caption
c [Block]
b) =
([Block] -> Figure) -> f [Block] -> f Figure
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Caption -> [Block] -> Figure
Figure Attr
a Caption
c) ([Block] -> f [Block]
f [Block]
b)
instance HasAttr Figure where
attr :: Lens' Figure Attr
attr Attr -> f Attr
f (Figure Attr
a Caption
c [Block]
b) =
(Attr -> Figure) -> f Attr -> f Figure
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Attr -> Caption -> [Block] -> Figure
Figure Attr
a' Caption
c [Block]
b) (Attr -> f Attr
f Attr
a)
instance HasCaption Figure where
caption :: Lens' Figure Caption
caption Caption -> f Caption
f (Figure Attr
a Caption
c [Block]
b) =
(Caption -> Figure) -> f Caption -> f Figure
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Caption
c' -> Attr -> Caption -> [Block] -> Figure
Figure Attr
a Caption
c' [Block]
b) (Caption -> f Caption
f Caption
c)
class AsFigure a where
_Figure ::
Prism' a Figure
instance AsFigure Figure where
_Figure :: Prism' Figure Figure
_Figure =
p Figure (f Figure) -> p Figure (f Figure)
forall a. a -> a
id
instance AsFigure Block where
_Figure :: Prism' Block Figure
_Figure =
(Figure -> Block) -> (Block -> Maybe Figure) -> Prism' Block Figure
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Figure -> Block
FigureBlock
(\case
FigureBlock Figure
i -> Figure -> Maybe Figure
forall a. a -> Maybe a
Just Figure
i
Block
_ -> Maybe Figure
forall a. Maybe a
Nothing)
instance AsFigure D.Block where
_Figure :: Prism' Block Figure
_Figure =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p Figure (f Figure) -> p Block (f Block))
-> p Figure (f Figure)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Figure (f Figure) -> p Block (f Block)
forall a. AsFigure a => Prism' a Figure
Prism' Block Figure
_Figure
data Div =
Div
Attr
[Block]
deriving (Div -> Div -> Bool
(Div -> Div -> Bool) -> (Div -> Div -> Bool) -> Eq Div
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Div -> Div -> Bool
== :: Div -> Div -> Bool
$c/= :: Div -> Div -> Bool
/= :: Div -> Div -> Bool
Eq, Eq Div
Eq Div =>
(Div -> Div -> Ordering)
-> (Div -> Div -> Bool)
-> (Div -> Div -> Bool)
-> (Div -> Div -> Bool)
-> (Div -> Div -> Bool)
-> (Div -> Div -> Div)
-> (Div -> Div -> Div)
-> Ord Div
Div -> Div -> Bool
Div -> Div -> Ordering
Div -> Div -> Div
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 :: Div -> Div -> Ordering
compare :: Div -> Div -> Ordering
$c< :: Div -> Div -> Bool
< :: Div -> Div -> Bool
$c<= :: Div -> Div -> Bool
<= :: Div -> Div -> Bool
$c> :: Div -> Div -> Bool
> :: Div -> Div -> Bool
$c>= :: Div -> Div -> Bool
>= :: Div -> Div -> Bool
$cmax :: Div -> Div -> Div
max :: Div -> Div -> Div
$cmin :: Div -> Div -> Div
min :: Div -> Div -> Div
Ord, Int -> Div -> ShowS
[Div] -> ShowS
Div -> String
(Int -> Div -> ShowS)
-> (Div -> String) -> ([Div] -> ShowS) -> Show Div
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Div -> ShowS
showsPrec :: Int -> Div -> ShowS
$cshow :: Div -> String
show :: Div -> String
$cshowList :: [Div] -> ShowS
showList :: [Div] -> ShowS
Show, Typeable Div
Typeable Div =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Div -> c Div)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Div)
-> (Div -> Constr)
-> (Div -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Div))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Div))
-> ((forall b. Data b => b -> b) -> Div -> Div)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r)
-> (forall u. (forall d. Data d => d -> u) -> Div -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Div -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Div -> m Div)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div)
-> Data Div
Div -> Constr
Div -> DataType
(forall b. Data b => b -> b) -> Div -> Div
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) -> Div -> u
forall u. (forall d. Data d => d -> u) -> Div -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Div -> m Div
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Div
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Div -> c Div
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Div)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Div)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Div -> c Div
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Div -> c Div
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Div
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Div
$ctoConstr :: Div -> Constr
toConstr :: Div -> Constr
$cdataTypeOf :: Div -> DataType
dataTypeOf :: Div -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Div)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Div)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Div)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Div)
$cgmapT :: (forall b. Data b => b -> b) -> Div -> Div
gmapT :: (forall b. Data b => b -> b) -> Div -> Div
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Div -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Div -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Div -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Div -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Div -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Div -> m Div
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Div -> m Div
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Div -> m Div
Data, Typeable, ReadPrec [Div]
ReadPrec Div
Int -> ReadS Div
ReadS [Div]
(Int -> ReadS Div)
-> ReadS [Div] -> ReadPrec Div -> ReadPrec [Div] -> Read Div
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Div
readsPrec :: Int -> ReadS Div
$creadList :: ReadS [Div]
readList :: ReadS [Div]
$creadPrec :: ReadPrec Div
readPrec :: ReadPrec Div
$creadListPrec :: ReadPrec [Div]
readListPrec :: ReadPrec [Div]
Read, (forall x. Div -> Rep Div x)
-> (forall x. Rep Div x -> Div) -> Generic Div
forall x. Rep Div x -> Div
forall x. Div -> Rep Div x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Div -> Rep Div x
from :: forall x. Div -> Rep Div x
$cto :: forall x. Rep Div x -> Div
to :: forall x. Rep Div x -> Div
Generic)
instance Semigroup Div where
Div Attr
a1 [Block]
b1 <> :: Div -> Div -> Div
<> Div Attr
a2 [Block]
b2 =
Attr -> [Block] -> Div
Div (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) ([Block]
b1 [Block] -> [Block] -> [Block]
forall a. Semigroup a => a -> a -> a
<> [Block]
b2)
instance Monoid Div where
mempty :: Div
mempty =
Attr -> [Block] -> Div
Div Attr
forall a. Monoid a => a
mempty [Block]
forall a. Monoid a => a
mempty
class HasDiv a where
div ::
Lens' a Div
instance HasDiv Div where
div :: Lens' Div Div
div =
(Div -> f Div) -> Div -> f Div
forall a. a -> a
id
instance HasBlocks Div where
blocks :: Lens' Div [Block]
blocks [Block] -> f [Block]
f (Div Attr
a [Block]
b) =
([Block] -> Div) -> f [Block] -> f Div
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Block] -> Div
Div Attr
a) ([Block] -> f [Block]
f [Block]
b)
class AsDiv a where
_Div ::
Prism' a Div
instance AsDiv Div where
_Div :: Prism' Div Div
_Div =
p Div (f Div) -> p Div (f Div)
forall a. a -> a
id
instance AsDiv Block where
_Div :: Prism' Block Div
_Div =
(Div -> Block) -> (Block -> Maybe Div) -> Prism' Block Div
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Div -> Block
DivBlock
(\case
DivBlock Div
x -> Div -> Maybe Div
forall a. a -> Maybe a
Just Div
x
Block
_ -> Maybe Div
forall a. Maybe a
Nothing)
instance AsDiv D.Block where
_Div :: Prism' Block Div
_Div =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock (p Block (f Block) -> p Block (f Block))
-> (p Div (f Div) -> p Block (f Block))
-> p Div (f Div)
-> p Block (f Block)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Div (f Div) -> p Block (f Block)
forall a. AsDiv a => Prism' a Div
Prism' Block Div
_Div
data Block =
Plain [Inline]
| Para [Inline]
| LineBlock [[Inline]]
| CodeBlock Code
| RawBlock Raw
| BlockQuote [Block]
| OrderedListBlock OrderedList
| BulletList [[Block]]
| DefinitionList [Definition]
| Header
| HorizontalRule
| TableBlock Table
| FigureBlock Figure
| DivBlock Div
deriving (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, 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, 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, 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, Typeable, ReadPrec [Block]
ReadPrec Block
Int -> ReadS Block
ReadS [Block]
(Int -> ReadS Block)
-> ReadS [Block]
-> ReadPrec Block
-> ReadPrec [Block]
-> Read Block
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Block
readsPrec :: Int -> ReadS Block
$creadList :: ReadS [Block]
readList :: ReadS [Block]
$creadPrec :: ReadPrec Block
readPrec :: ReadPrec Block
$creadListPrec :: ReadPrec [Block]
readListPrec :: ReadPrec [Block]
Read, (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)
class HasBlock a where
block ::
Lens' a Block
instance HasBlock Block where
block :: Lens' Block Block
block =
(Block -> f Block) -> Block -> f Block
forall a. a -> a
id
instance HasBlock D.Block where
block :: Lens' Block Block
block =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock
class AsBlock a where
_Block ::
Prism' a Block
_Plain ::
Prism' a [Inline]
_Plain =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Block (f Block))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Block (f Block)
forall a. AsBlock a => Prism' a [Inline]
Prism' Block [Inline]
_Plain
_Para ::
Prism' a [Inline]
_Para =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Block (f Block))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Block (f Block)
forall a. AsBlock a => Prism' a [Inline]
Prism' Block [Inline]
_Para
_LineBlock ::
Prism' a [[Inline]]
_LineBlock =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p [[Inline]] (f [[Inline]]) -> p Block (f Block))
-> p [[Inline]] (f [[Inline]])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [[Inline]] (f [[Inline]]) -> p Block (f Block)
forall a. AsBlock a => Prism' a [[Inline]]
Prism' Block [[Inline]]
_LineBlock
_BlockQuote ::
Prism' a [Block]
_BlockQuote =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p [Block] (f [Block]) -> p Block (f Block))
-> p [Block] (f [Block])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Block] (f [Block]) -> p Block (f Block)
forall a. AsBlock a => Prism' a [Block]
Prism' Block [Block]
_BlockQuote
_BulletList ::
Prism' a [[Block]]
_BulletList =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p [[Block]] (f [[Block]]) -> p Block (f Block))
-> p [[Block]] (f [[Block]])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [[Block]] (f [[Block]]) -> p Block (f Block)
forall a. AsBlock a => Prism' a [[Block]]
Prism' Block [[Block]]
_BulletList
_DefinitionList ::
Prism' a [Definition]
_DefinitionList =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p [Definition] (f [Definition]) -> p Block (f Block))
-> p [Definition] (f [Definition])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Definition] (f [Definition]) -> p Block (f Block)
forall a. AsBlock a => Prism' a [Definition]
Prism' Block [Definition]
_DefinitionList
_HorizontalRule ::
Prism' a ()
_HorizontalRule =
p Block (f Block) -> p a (f a)
forall a. AsBlock a => Prism' a Block
Prism' a Block
_Block (p Block (f Block) -> p a (f a))
-> (p () (f ()) -> p Block (f Block)) -> p () (f ()) -> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Block (f Block)
forall a. AsBlock a => Prism' a ()
Prism' Block ()
_HorizontalRule
instance AsBlock Block where
_Block :: Prism' Block Block
_Block =
p Block (f Block) -> p Block (f Block)
forall a. a -> a
id
_Plain :: Prism' Block [Inline]
_Plain =
([Inline] -> Block)
-> (Block -> Maybe [Inline]) -> Prism' Block [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Block
Plain
(\case
Plain [Inline]
i -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
i
Block
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Para :: Prism' Block [Inline]
_Para =
([Inline] -> Block)
-> (Block -> Maybe [Inline]) -> Prism' Block [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Block
Para
(\case
Para [Inline]
i -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
i
Block
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_LineBlock :: Prism' Block [[Inline]]
_LineBlock =
([[Inline]] -> Block)
-> (Block -> Maybe [[Inline]]) -> Prism' Block [[Inline]]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[[Inline]] -> Block
LineBlock
(\case
LineBlock [[Inline]]
i -> [[Inline]] -> Maybe [[Inline]]
forall a. a -> Maybe a
Just [[Inline]]
i
Block
_ -> Maybe [[Inline]]
forall a. Maybe a
Nothing)
_BlockQuote :: Prism' Block [Block]
_BlockQuote =
([Block] -> Block)
-> (Block -> Maybe [Block]) -> Prism' Block [Block]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Block] -> Block
BlockQuote
(\case
BlockQuote [Block]
i -> [Block] -> Maybe [Block]
forall a. a -> Maybe a
Just [Block]
i
Block
_ -> Maybe [Block]
forall a. Maybe a
Nothing)
_BulletList :: Prism' Block [[Block]]
_BulletList =
([[Block]] -> Block)
-> (Block -> Maybe [[Block]]) -> Prism' Block [[Block]]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[[Block]] -> Block
BulletList
(\case
BulletList [[Block]]
i -> [[Block]] -> Maybe [[Block]]
forall a. a -> Maybe a
Just [[Block]]
i
Block
_ -> Maybe [[Block]]
forall a. Maybe a
Nothing)
_DefinitionList :: Prism' Block [Definition]
_DefinitionList =
([Definition] -> Block)
-> (Block -> Maybe [Definition]) -> Prism' Block [Definition]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Definition] -> Block
DefinitionList
(\case
DefinitionList [Definition]
i -> [Definition] -> Maybe [Definition]
forall a. a -> Maybe a
Just [Definition]
i
Block
_ -> Maybe [Definition]
forall a. Maybe a
Nothing)
_HorizontalRule :: Prism' Block ()
_HorizontalRule =
(() -> Block) -> (Block -> Maybe ()) -> Prism' Block ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Block
HorizontalRule)
(\case
Block
HorizontalRule -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Block
_ -> Maybe ()
forall a. Maybe a
Nothing)
instance AsBlock D.Block where
_Block :: Prism' Block Block
_Block =
AnIso Block Block Block Block -> Iso Block Block Block Block
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Block Block Block Block
Iso' Block Block
isBlock
instance Plated Block where
plate :: Traversal' Block Block
plate Block -> f Block
_ (Plain [Inline]
i) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Inline] -> Block
Plain [Inline]
i)
plate Block -> f Block
_ (Para [Inline]
i) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Inline] -> Block
Para [Inline]
i)
plate Block -> f Block
_ (LineBlock [[Inline]]
i) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([[Inline]] -> Block
LineBlock [[Inline]]
i)
plate Block -> f Block
_ (CodeBlock Code
x) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Code -> Block
CodeBlock Code
x)
plate Block -> f Block
_ (RawBlock Raw
x) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Raw -> Block
RawBlock Raw
x)
plate Block -> f Block
f (BlockQuote [Block]
b) =
[Block] -> Block
BlockQuote ([Block] -> Block) -> f [Block] -> f Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> f Block) -> [Block] -> f [Block]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Block -> f Block
f [Block]
b
plate Block -> f Block
f (OrderedListBlock OrderedList
x) =
OrderedList -> Block
OrderedListBlock (OrderedList -> Block)
-> ([[Block]] -> OrderedList) -> [[Block]] -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListAttributes -> [[Block]] -> OrderedList
OrderedList (Getting ListAttributes OrderedList ListAttributes
-> OrderedList -> ListAttributes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListAttributes OrderedList ListAttributes
forall a. HasListAttributes a => Lens' a ListAttributes
Lens' OrderedList ListAttributes
listAttributes OrderedList
x) ([[Block]] -> Block) -> f [[Block]] -> f Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Block] -> f [Block]) -> [[Block]] -> f [[Block]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((Block -> f Block) -> [Block] -> f [Block]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Block -> f Block
f) (Getting [[Block]] OrderedList [[Block]] -> OrderedList -> [[Block]]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting [[Block]] OrderedList [[Block]]
forall a. HasOrderedList a => Lens' a [[Block]]
Lens' OrderedList [[Block]]
orderedListBlocks OrderedList
x)
plate Block -> f Block
f (BulletList [[Block]]
b) =
[[Block]] -> Block
BulletList ([[Block]] -> Block) -> f [[Block]] -> f Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Block] -> f [Block]) -> [[Block]] -> f [[Block]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((Block -> f Block) -> [Block] -> f [Block]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Block -> f Block
f) [[Block]]
b
plate Block -> f Block
f (DefinitionList [Definition]
x) =
[Definition] -> Block
DefinitionList ([Definition] -> Block) -> f [Definition] -> f Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Definition -> f Definition) -> [Definition] -> f [Definition]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\(Definition [Inline]
i [[Block]]
b) -> [Inline] -> [[Block]] -> Definition
Definition [Inline]
i ([[Block]] -> Definition) -> f [[Block]] -> f Definition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Block] -> f [Block]) -> [[Block]] -> f [[Block]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((Block -> f Block) -> [Block] -> f [Block]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Block -> f Block
f) [[Block]]
b) [Definition]
x
plate Block -> f Block
_ (HeaderBlock Header
x) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Header -> Block
HeaderBlock Header
x)
plate Block -> f Block
_ Block
HorizontalRule =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Block
HorizontalRule
plate Block -> f Block
_ (TableBlock Table
x) =
Block -> f Block
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Table -> Block
TableBlock Table
x)
plate Block -> f Block
f (FigureBlock (Figure Attr
a Caption
c [Block]
b)) =
Figure -> Block
FigureBlock (Figure -> Block) -> ([Block] -> Figure) -> [Block] -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Caption -> [Block] -> Figure
Figure Attr
a Caption
c ([Block] -> Block) -> f [Block] -> f Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> f Block) -> [Block] -> f [Block]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Block -> f Block
f [Block]
b
plate Block -> f Block
f (DivBlock (Div Attr
a [Block]
b)) =
Div -> Block
DivBlock (Div -> Block) -> ([Block] -> Div) -> [Block] -> Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Block] -> Div
Div Attr
a ([Block] -> Block) -> f [Block] -> f Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> f Block) -> [Block] -> f [Block]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Block -> f Block
f [Block]
b
isBlock ::
Iso'
Block
D.Block
isBlock :: Iso' Block Block
isBlock =
(Block -> Block) -> (Block -> Block) -> Iso' Block Block
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
Plain [Inline]
i -> ShortCaption -> Block
D.Plain ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
Para [Inline]
i -> ShortCaption -> Block
D.Para ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
LineBlock [[Inline]]
i -> [ShortCaption] -> Block
D.LineBlock (([Inline] -> ShortCaption) -> [[Inline]] -> [ShortCaption]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline)) [[Inline]]
i)
CodeBlock (Code Attr
a Text
t) -> Attr -> Text -> Block
D.CodeBlock (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) Text
t
RawBlock (Raw Format
f Text
t) -> Format -> Text -> Block
D.RawBlock (Getting Format Format Format -> Format -> Format
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Format Format Format
Iso Format Format Format Format
isFormat Format
f) Text
t
BlockQuote [Block]
b -> [Block] -> Block
D.BlockQuote ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b)
OrderedListBlock (OrderedList ListAttributes
a [[Block]]
b) -> ListAttributes -> [[Block]] -> Block
D.OrderedList (Getting ListAttributes ListAttributes ListAttributes
-> ListAttributes -> ListAttributes
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ListAttributes ListAttributes ListAttributes
Iso' ListAttributes ListAttributes
isListAttributes ListAttributes
a) (([Block] -> [Block]) -> [[Block]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock)) [[Block]]
b)
BulletList [[Block]]
b -> [[Block]] -> Block
D.BulletList (([Block] -> [Block]) -> [[Block]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock)) [[Block]]
b)
DefinitionList [Definition]
x -> [(ShortCaption, [[Block]])] -> Block
D.DefinitionList ((Definition -> (ShortCaption, [[Block]]))
-> [Definition] -> [(ShortCaption, [[Block]])]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Definition [Inline]
i [[Block]]
b) -> ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i, ([Block] -> [Block]) -> [[Block]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock)) [[Block]]
b)) [Definition]
x)
HeaderBlock Header
h -> Int -> Attr -> ShortCaption -> Block
D.Header (Getting Int Header Int -> Header -> Int
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Int Header Int
forall a. HasHeader a => Lens' a Int
Lens' Header Int
headerLevel Header
h) (Getting Attr Header Attr -> Header -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view ((Attr -> Const Attr Attr) -> Header -> Const Attr Header
forall a. HasAttr a => Lens' a Attr
Lens' Header Attr
attr ((Attr -> Const Attr Attr) -> Header -> Const Attr Header)
-> Getting Attr Attr Attr -> Getting Attr Header Attr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Attr Attr Attr
Iso' Attr Attr
isAttr) Header
h) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) (Getting [Inline] Header [Inline] -> Header -> [Inline]
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting [Inline] Header [Inline]
forall a. HasInlines a => Lens' a [Inline]
Lens' Header [Inline]
inlines Header
h))
Block
HorizontalRule -> Block
D.HorizontalRule
TableBlock (Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
f) -> Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
D.Table (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) (Getting Caption Caption Caption -> Caption -> Caption
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Caption Caption Caption
Iso' Caption Caption
isCaption Caption
c) ((ColSpec -> ColSpec) -> [ColSpec] -> [ColSpec]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting ColSpec ColSpec ColSpec -> ColSpec -> ColSpec
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ColSpec ColSpec ColSpec
Iso' ColSpec ColSpec
isColSpec) [ColSpec]
s) (Getting TableHead TableHead TableHead -> TableHead -> TableHead
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting TableHead TableHead TableHead
Iso' TableHead TableHead
isTableHead TableHead
h) ((TableBody -> TableBody) -> [TableBody] -> [TableBody]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting TableBody TableBody TableBody -> TableBody -> TableBody
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting TableBody TableBody TableBody
Iso' TableBody TableBody
isTableBody) [TableBody]
b) (Getting TableFoot TableFoot TableFoot -> TableFoot -> TableFoot
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting TableFoot TableFoot TableFoot
Iso' TableFoot TableFoot
isTableFoot TableFoot
f)
FigureBlock (Figure Attr
a Caption
c [Block]
b) -> Attr -> Caption -> [Block] -> Block
D.Figure (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) (Getting Caption Caption Caption -> Caption -> Caption
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Caption Caption Caption
Iso' Caption Caption
isCaption Caption
c) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b)
DivBlock (Div Attr
a [Block]
b) -> Attr -> [Block] -> Block
D.Div (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b)
)
(\case
D.Plain ShortCaption
i -> [Inline] -> Block
Plain ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Para ShortCaption
i -> [Inline] -> Block
Para ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.LineBlock [ShortCaption]
i -> [[Inline]] -> Block
LineBlock ((ShortCaption -> [Inline]) -> [ShortCaption] -> [[Inline]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline)) [ShortCaption]
i)
D.CodeBlock Attr
a Text
t -> Code -> Block
CodeBlock (Attr -> Text -> Code
Code (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) Text
t)
D.RawBlock Format
f Text
t -> Raw -> Block
RawBlock (Format -> Text -> Raw
Raw (AReview Format Format -> Format -> Format
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Format Format
Iso Format Format Format Format
isFormat Format
f) Text
t)
D.BlockQuote [Block]
b -> [Block] -> Block
BlockQuote ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b)
D.OrderedList ListAttributes
a [[Block]]
b -> OrderedList -> Block
OrderedListBlock (ListAttributes -> [[Block]] -> OrderedList
OrderedList (AReview ListAttributes ListAttributes
-> ListAttributes -> ListAttributes
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ListAttributes ListAttributes
Iso' ListAttributes ListAttributes
isListAttributes ListAttributes
a) (([Block] -> [Block]) -> [[Block]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock)) [[Block]]
b))
D.BulletList [[Block]]
b -> [[Block]] -> Block
BulletList (([Block] -> [Block]) -> [[Block]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock)) [[Block]]
b)
D.DefinitionList [(ShortCaption, [[Block]])]
x -> [Definition] -> Block
DefinitionList (((ShortCaption, [[Block]]) -> Definition)
-> [(ShortCaption, [[Block]])] -> [Definition]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(ShortCaption
i, [[Block]]
b) -> [Inline] -> [[Block]] -> Definition
Definition ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i) (([Block] -> [Block]) -> [[Block]] -> [[Block]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock)) [[Block]]
b)) [(ShortCaption, [[Block]])]
x)
D.Header Int
n Attr
a ShortCaption
i -> Header -> Block
HeaderBlock (Int -> Attr -> [Inline] -> Header
Header Int
n (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i))
Block
D.HorizontalRule -> Block
HorizontalRule
D.Table Attr
a Caption
c [ColSpec]
s TableHead
h [TableBody]
b TableFoot
f -> Table -> Block
TableBlock (Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) (AReview Caption Caption -> Caption -> Caption
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Caption Caption
Iso' Caption Caption
isCaption Caption
c) ((ColSpec -> ColSpec) -> [ColSpec] -> [ColSpec]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview ColSpec ColSpec -> ColSpec -> ColSpec
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview ColSpec ColSpec
Iso' ColSpec ColSpec
isColSpec) [ColSpec]
s) (AReview TableHead TableHead -> TableHead -> TableHead
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview TableHead TableHead
Iso' TableHead TableHead
isTableHead TableHead
h) ((TableBody -> TableBody) -> [TableBody] -> [TableBody]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview TableBody TableBody -> TableBody -> TableBody
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview TableBody TableBody
Iso' TableBody TableBody
isTableBody) [TableBody]
b) (AReview TableFoot TableFoot -> TableFoot -> TableFoot
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview TableFoot TableFoot
Iso' TableFoot TableFoot
isTableFoot TableFoot
f))
D.Figure Attr
a Caption
c [Block]
b -> Figure -> Block
FigureBlock (Attr -> Caption -> [Block] -> Figure
Figure (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) (AReview Caption Caption -> Caption -> Caption
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Caption Caption
Iso' Caption Caption
isCaption Caption
c) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b))
D.Div Attr
a [Block]
b -> Div -> Block
DivBlock (Attr -> [Block] -> Div
Div (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b))
)
instance Walkable D.Block Block where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Block -> m Block) -> Block -> m Block
walkM =
(Block -> m Block) -> Block -> m Block
Iso' Block Block
isBlock
query :: forall c. Monoid c => (Block -> c) -> Block -> c
query Block -> c
f =
Block -> c
f (Block -> c) -> (Block -> Block) -> Block -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock
data MathType =
DisplayMath
| InlineMath
deriving (MathType -> MathType -> Bool
(MathType -> MathType -> Bool)
-> (MathType -> MathType -> Bool) -> Eq MathType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MathType -> MathType -> Bool
== :: MathType -> MathType -> Bool
$c/= :: MathType -> MathType -> Bool
/= :: MathType -> MathType -> Bool
Eq, Eq MathType
Eq MathType =>
(MathType -> MathType -> Ordering)
-> (MathType -> MathType -> Bool)
-> (MathType -> MathType -> Bool)
-> (MathType -> MathType -> Bool)
-> (MathType -> MathType -> Bool)
-> (MathType -> MathType -> MathType)
-> (MathType -> MathType -> MathType)
-> Ord MathType
MathType -> MathType -> Bool
MathType -> MathType -> Ordering
MathType -> MathType -> MathType
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 :: MathType -> MathType -> Ordering
compare :: MathType -> MathType -> Ordering
$c< :: MathType -> MathType -> Bool
< :: MathType -> MathType -> Bool
$c<= :: MathType -> MathType -> Bool
<= :: MathType -> MathType -> Bool
$c> :: MathType -> MathType -> Bool
> :: MathType -> MathType -> Bool
$c>= :: MathType -> MathType -> Bool
>= :: MathType -> MathType -> Bool
$cmax :: MathType -> MathType -> MathType
max :: MathType -> MathType -> MathType
$cmin :: MathType -> MathType -> MathType
min :: MathType -> MathType -> MathType
Ord, Int -> MathType -> ShowS
[MathType] -> ShowS
MathType -> String
(Int -> MathType -> ShowS)
-> (MathType -> String) -> ([MathType] -> ShowS) -> Show MathType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MathType -> ShowS
showsPrec :: Int -> MathType -> ShowS
$cshow :: MathType -> String
show :: MathType -> String
$cshowList :: [MathType] -> ShowS
showList :: [MathType] -> ShowS
Show, Typeable MathType
Typeable MathType =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathType -> c MathType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathType)
-> (MathType -> Constr)
-> (MathType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType))
-> ((forall b. Data b => b -> b) -> MathType -> MathType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r)
-> (forall u. (forall d. Data d => d -> u) -> MathType -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> MathType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType)
-> Data MathType
MathType -> Constr
MathType -> DataType
(forall b. Data b => b -> b) -> MathType -> MathType
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) -> MathType -> u
forall u. (forall d. Data d => d -> u) -> MathType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathType -> c MathType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathType -> c MathType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MathType -> c MathType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MathType
$ctoConstr :: MathType -> Constr
toConstr :: MathType -> Constr
$cdataTypeOf :: MathType -> DataType
dataTypeOf :: MathType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MathType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MathType)
$cgmapT :: (forall b. Data b => b -> b) -> MathType -> MathType
gmapT :: (forall b. Data b => b -> b) -> MathType -> MathType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MathType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MathType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MathType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MathType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MathType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MathType -> m MathType
Data, Typeable, ReadPrec [MathType]
ReadPrec MathType
Int -> ReadS MathType
ReadS [MathType]
(Int -> ReadS MathType)
-> ReadS [MathType]
-> ReadPrec MathType
-> ReadPrec [MathType]
-> Read MathType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MathType
readsPrec :: Int -> ReadS MathType
$creadList :: ReadS [MathType]
readList :: ReadS [MathType]
$creadPrec :: ReadPrec MathType
readPrec :: ReadPrec MathType
$creadListPrec :: ReadPrec [MathType]
readListPrec :: ReadPrec [MathType]
Read, (forall x. MathType -> Rep MathType x)
-> (forall x. Rep MathType x -> MathType) -> Generic MathType
forall x. Rep MathType x -> MathType
forall x. MathType -> Rep MathType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MathType -> Rep MathType x
from :: forall x. MathType -> Rep MathType x
$cto :: forall x. Rep MathType x -> MathType
to :: forall x. Rep MathType x -> MathType
Generic)
class HasMathType a where
mathType ::
Lens' a MathType
instance HasMathType MathType where
mathType :: Lens' MathType MathType
mathType =
(MathType -> f MathType) -> MathType -> f MathType
forall a. a -> a
id
instance HasMathType D.MathType where
mathType :: Lens' MathType MathType
mathType =
AnIso MathType MathType MathType MathType
-> Iso MathType MathType MathType MathType
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso MathType MathType MathType MathType
Iso' MathType MathType
isMathType
class AsMathType a where
_MathType ::
Prism' a MathType
_DisplayMath ::
Prism' a ()
_DisplayMath =
p MathType (f MathType) -> p a (f a)
forall a. AsMathType a => Prism' a MathType
Prism' a MathType
_MathType (p MathType (f MathType) -> p a (f a))
-> (p () (f ()) -> p MathType (f MathType))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p MathType (f MathType)
forall a. AsMathType a => Prism' a ()
Prism' MathType ()
_DisplayMath
_InlineMath ::
Prism' a ()
_InlineMath =
p MathType (f MathType) -> p a (f a)
forall a. AsMathType a => Prism' a MathType
Prism' a MathType
_MathType (p MathType (f MathType) -> p a (f a))
-> (p () (f ()) -> p MathType (f MathType))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p MathType (f MathType)
forall a. AsMathType a => Prism' a ()
Prism' MathType ()
_InlineMath
instance AsMathType MathType where
_MathType :: Prism' MathType MathType
_MathType =
p MathType (f MathType) -> p MathType (f MathType)
forall a. a -> a
id
_DisplayMath :: Prism' MathType ()
_DisplayMath =
(() -> MathType) -> (MathType -> Maybe ()) -> Prism' MathType ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> MathType
DisplayMath)
(\case
MathType
DisplayMath -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
MathType
_ -> Maybe ()
forall a. Maybe a
Nothing)
_InlineMath :: Prism' MathType ()
_InlineMath =
(() -> MathType) -> (MathType -> Maybe ()) -> Prism' MathType ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> MathType
InlineMath)
(\case
MathType
InlineMath -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
MathType
_ -> Maybe ()
forall a. Maybe a
Nothing)
instance AsMathType D.MathType where
_MathType :: Prism' MathType MathType
_MathType =
AnIso MathType MathType MathType MathType
-> Iso MathType MathType MathType MathType
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso MathType MathType MathType MathType
Iso' MathType MathType
isMathType
isMathType ::
Iso'
MathType
D.MathType
isMathType :: Iso' MathType MathType
isMathType =
(MathType -> MathType)
-> (MathType -> MathType) -> Iso' MathType MathType
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
MathType
DisplayMath -> MathType
D.DisplayMath
MathType
InlineMath -> MathType
D.InlineMath
)
(\case
MathType
D.DisplayMath -> MathType
DisplayMath
MathType
D.InlineMath -> MathType
InlineMath
)
instance Walkable D.MathType MathType where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(MathType -> m MathType) -> MathType -> m MathType
walkM =
(MathType -> m MathType) -> MathType -> m MathType
Iso' MathType MathType
isMathType
query :: forall c. Monoid c => (MathType -> c) -> MathType -> c
query MathType -> c
f =
MathType -> c
f (MathType -> c) -> (MathType -> MathType) -> MathType -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting MathType MathType MathType -> MathType -> MathType
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting MathType MathType MathType
Iso' MathType MathType
isMathType
newtype Meta =
Meta (Map Text MetaValue)
deriving (Meta -> Meta -> Bool
(Meta -> Meta -> Bool) -> (Meta -> Meta -> Bool) -> Eq Meta
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Meta -> Meta -> Bool
== :: Meta -> Meta -> Bool
$c/= :: Meta -> Meta -> Bool
/= :: Meta -> Meta -> Bool
Eq, Eq Meta
Eq Meta =>
(Meta -> Meta -> Ordering)
-> (Meta -> Meta -> Bool)
-> (Meta -> Meta -> Bool)
-> (Meta -> Meta -> Bool)
-> (Meta -> Meta -> Bool)
-> (Meta -> Meta -> Meta)
-> (Meta -> Meta -> Meta)
-> Ord Meta
Meta -> Meta -> Bool
Meta -> Meta -> Ordering
Meta -> Meta -> Meta
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 :: Meta -> Meta -> Ordering
compare :: Meta -> Meta -> Ordering
$c< :: Meta -> Meta -> Bool
< :: Meta -> Meta -> Bool
$c<= :: Meta -> Meta -> Bool
<= :: Meta -> Meta -> Bool
$c> :: Meta -> Meta -> Bool
> :: Meta -> Meta -> Bool
$c>= :: Meta -> Meta -> Bool
>= :: Meta -> Meta -> Bool
$cmax :: Meta -> Meta -> Meta
max :: Meta -> Meta -> Meta
$cmin :: Meta -> Meta -> Meta
min :: Meta -> Meta -> Meta
Ord, Int -> Meta -> ShowS
[Meta] -> ShowS
Meta -> String
(Int -> Meta -> ShowS)
-> (Meta -> String) -> ([Meta] -> ShowS) -> Show Meta
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Meta -> ShowS
showsPrec :: Int -> Meta -> ShowS
$cshow :: Meta -> String
show :: Meta -> String
$cshowList :: [Meta] -> ShowS
showList :: [Meta] -> ShowS
Show, Typeable Meta
Typeable Meta =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Meta -> c Meta)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Meta)
-> (Meta -> Constr)
-> (Meta -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Meta))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta))
-> ((forall b. Data b => b -> b) -> Meta -> Meta)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r)
-> (forall u. (forall d. Data d => d -> u) -> Meta -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Meta -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta)
-> Data Meta
Meta -> Constr
Meta -> DataType
(forall b. Data b => b -> b) -> Meta -> Meta
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) -> Meta -> u
forall u. (forall d. Data d => d -> u) -> Meta -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Meta
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Meta -> c Meta
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Meta)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Meta -> c Meta
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Meta -> c Meta
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Meta
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Meta
$ctoConstr :: Meta -> Constr
toConstr :: Meta -> Constr
$cdataTypeOf :: Meta -> DataType
dataTypeOf :: Meta -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Meta)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Meta)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Meta)
$cgmapT :: (forall b. Data b => b -> b) -> Meta -> Meta
gmapT :: (forall b. Data b => b -> b) -> Meta -> Meta
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meta -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Meta -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Meta -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Meta -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Meta -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Meta -> m Meta
Data, Typeable, ReadPrec [Meta]
ReadPrec Meta
Int -> ReadS Meta
ReadS [Meta]
(Int -> ReadS Meta)
-> ReadS [Meta] -> ReadPrec Meta -> ReadPrec [Meta] -> Read Meta
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Meta
readsPrec :: Int -> ReadS Meta
$creadList :: ReadS [Meta]
readList :: ReadS [Meta]
$creadPrec :: ReadPrec Meta
readPrec :: ReadPrec Meta
$creadListPrec :: ReadPrec [Meta]
readListPrec :: ReadPrec [Meta]
Read, (forall x. Meta -> Rep Meta x)
-> (forall x. Rep Meta x -> Meta) -> Generic Meta
forall x. Rep Meta x -> Meta
forall x. Meta -> Rep Meta x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Meta -> Rep Meta x
from :: forall x. Meta -> Rep Meta x
$cto :: forall x. Rep Meta x -> Meta
to :: forall x. Rep Meta x -> Meta
Generic)
instance (Meta ~ t) => Rewrapped Meta t
instance Wrapped Meta where
type Unwrapped Meta =
(Map Text MetaValue)
_Wrapped' :: Iso' Meta (Unwrapped Meta)
_Wrapped' =
(Meta -> Map Text MetaValue)
-> (Map Text MetaValue -> Meta)
-> Iso Meta Meta (Map Text MetaValue) (Map Text MetaValue)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(Meta Map Text MetaValue
x) -> Map Text MetaValue
x) Map Text MetaValue -> Meta
Meta
type instance Index Meta = Text
type instance IxValue Meta = MetaValue
instance Ixed Meta where
ix :: Index Meta -> Traversal' Meta (IxValue Meta)
ix Index Meta
i =
(Unwrapped Meta -> f (Unwrapped Meta)) -> Meta -> f Meta
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso' Meta (Unwrapped Meta)
_Wrapped ((Unwrapped Meta -> f (Unwrapped Meta)) -> Meta -> f Meta)
-> ((MetaValue -> f MetaValue)
-> Unwrapped Meta -> f (Unwrapped Meta))
-> (MetaValue -> f MetaValue)
-> Meta
-> f Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Unwrapped Meta)
-> Traversal' (Unwrapped Meta) (IxValue (Unwrapped Meta))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (Unwrapped Meta)
Index Meta
i
instance At Meta where
at :: Index Meta -> Lens' Meta (Maybe (IxValue Meta))
at Index Meta
k =
(Unwrapped Meta -> f (Unwrapped Meta)) -> Meta -> f Meta
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso' Meta (Unwrapped Meta)
_Wrapped ((Unwrapped Meta -> f (Unwrapped Meta)) -> Meta -> f Meta)
-> ((Maybe MetaValue -> f (Maybe MetaValue))
-> Unwrapped Meta -> f (Unwrapped Meta))
-> (Maybe MetaValue -> f (Maybe MetaValue))
-> Meta
-> f Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Unwrapped Meta)
-> Lens' (Unwrapped Meta) (Maybe (IxValue (Unwrapped Meta)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index (Unwrapped Meta)
Index Meta
k
instance Each Meta Meta MetaValue MetaValue where
each :: Traversal Meta Meta MetaValue MetaValue
each =
(Unwrapped Meta -> f (Unwrapped Meta)) -> Meta -> f Meta
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso' Meta (Unwrapped Meta)
_Wrapped ((Unwrapped Meta -> f (Unwrapped Meta)) -> Meta -> f Meta)
-> ((MetaValue -> f MetaValue)
-> Unwrapped Meta -> f (Unwrapped Meta))
-> (MetaValue -> f MetaValue)
-> Meta
-> f Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MetaValue -> f MetaValue) -> Unwrapped Meta -> f (Unwrapped Meta)
forall s t a b. Each s t a b => Traversal s t a b
Traversal (Unwrapped Meta) (Unwrapped Meta) MetaValue MetaValue
each
instance AsEmpty Meta where
_Empty :: Prism' Meta ()
_Empty =
p (Map Text MetaValue) (f (Map Text MetaValue)) -> p Meta (f Meta)
p (Unwrapped Meta) (f (Unwrapped Meta)) -> p Meta (f Meta)
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso' Meta (Unwrapped Meta)
_Wrapped (p (Map Text MetaValue) (f (Map Text MetaValue))
-> p Meta (f Meta))
-> (p () (f ()) -> p (Map Text MetaValue) (f (Map Text MetaValue)))
-> p () (f ())
-> p Meta (f Meta)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p (Map Text MetaValue) (f (Map Text MetaValue))
forall a. AsEmpty a => Prism' a ()
Prism' (Map Text MetaValue) ()
_Empty
class HasMeta a where
meta ::
Lens' a Meta
instance HasMeta Meta where
meta :: Lens' Meta Meta
meta =
(Meta -> f Meta) -> Meta -> f Meta
forall a. a -> a
id
instance HasMeta D.Meta where
meta :: Lens' Meta Meta
meta =
AnIso Meta Meta Meta Meta -> Iso Meta Meta Meta Meta
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Meta Meta Meta Meta
Iso' Meta Meta
isMeta
class AsMeta a where
_Meta ::
Prism' a Meta
instance AsMeta Meta where
_Meta :: Prism' Meta Meta
_Meta =
p Meta (f Meta) -> p Meta (f Meta)
forall a. a -> a
id
instance AsMeta D.Meta where
_Meta :: Prism' Meta Meta
_Meta =
AnIso Meta Meta Meta Meta -> Iso Meta Meta Meta Meta
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Meta Meta Meta Meta
Iso' Meta Meta
isMeta
isMeta ::
Iso'
Meta
D.Meta
isMeta :: Iso' Meta Meta
isMeta =
(Meta -> Meta) -> (Meta -> Meta) -> Iso' Meta Meta
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Meta Map Text MetaValue
x) -> Map Text MetaValue -> Meta
D.Meta ((MetaValue -> MetaValue)
-> Map Text MetaValue -> Map Text MetaValue
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (Getting MetaValue MetaValue MetaValue -> MetaValue -> MetaValue
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting MetaValue MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue) Map Text MetaValue
x))
(\(D.Meta Map Text MetaValue
x) -> Map Text MetaValue -> Meta
Meta ((MetaValue -> MetaValue)
-> Map Text MetaValue -> Map Text MetaValue
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (AReview MetaValue MetaValue -> MetaValue -> MetaValue
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue) Map Text MetaValue
x))
instance Walkable D.Meta Meta where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Meta -> m Meta) -> Meta -> m Meta
walkM =
(Meta -> m Meta) -> Meta -> m Meta
Iso' Meta Meta
isMeta
query :: forall c. Monoid c => (Meta -> c) -> Meta -> c
query Meta -> c
f =
Meta -> c
f (Meta -> c) -> (Meta -> Meta) -> Meta -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Meta Meta Meta -> Meta -> Meta
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Meta Meta Meta
Iso' Meta Meta
isMeta
instance Semigroup Meta where
Meta Map Text MetaValue
x <> :: Meta -> Meta -> Meta
<> Meta Map Text MetaValue
y =
Map Text MetaValue -> Meta
Meta (Map Text MetaValue -> Map Text MetaValue -> Map Text MetaValue
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map Text MetaValue
y Map Text MetaValue
x)
instance Monoid Meta where
mempty :: Meta
mempty =
Map Text MetaValue -> Meta
Meta Map Text MetaValue
forall a. Monoid a => a
mempty
data MetaValue =
MetaMap (Map Text MetaValue)
| MetaList [MetaValue]
| MetaBool Bool
| MetaString Text
| MetaInlines [Inline]
| MetaBlocks [Block]
deriving (MetaValue -> MetaValue -> Bool
(MetaValue -> MetaValue -> Bool)
-> (MetaValue -> MetaValue -> Bool) -> Eq MetaValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetaValue -> MetaValue -> Bool
== :: MetaValue -> MetaValue -> Bool
$c/= :: MetaValue -> MetaValue -> Bool
/= :: MetaValue -> MetaValue -> Bool
Eq, Eq MetaValue
Eq MetaValue =>
(MetaValue -> MetaValue -> Ordering)
-> (MetaValue -> MetaValue -> Bool)
-> (MetaValue -> MetaValue -> Bool)
-> (MetaValue -> MetaValue -> Bool)
-> (MetaValue -> MetaValue -> Bool)
-> (MetaValue -> MetaValue -> MetaValue)
-> (MetaValue -> MetaValue -> MetaValue)
-> Ord MetaValue
MetaValue -> MetaValue -> Bool
MetaValue -> MetaValue -> Ordering
MetaValue -> MetaValue -> MetaValue
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 :: MetaValue -> MetaValue -> Ordering
compare :: MetaValue -> MetaValue -> Ordering
$c< :: MetaValue -> MetaValue -> Bool
< :: MetaValue -> MetaValue -> Bool
$c<= :: MetaValue -> MetaValue -> Bool
<= :: MetaValue -> MetaValue -> Bool
$c> :: MetaValue -> MetaValue -> Bool
> :: MetaValue -> MetaValue -> Bool
$c>= :: MetaValue -> MetaValue -> Bool
>= :: MetaValue -> MetaValue -> Bool
$cmax :: MetaValue -> MetaValue -> MetaValue
max :: MetaValue -> MetaValue -> MetaValue
$cmin :: MetaValue -> MetaValue -> MetaValue
min :: MetaValue -> MetaValue -> MetaValue
Ord, Int -> MetaValue -> ShowS
[MetaValue] -> ShowS
MetaValue -> String
(Int -> MetaValue -> ShowS)
-> (MetaValue -> String)
-> ([MetaValue] -> ShowS)
-> Show MetaValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetaValue -> ShowS
showsPrec :: Int -> MetaValue -> ShowS
$cshow :: MetaValue -> String
show :: MetaValue -> String
$cshowList :: [MetaValue] -> ShowS
showList :: [MetaValue] -> ShowS
Show, Typeable MetaValue
Typeable MetaValue =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaValue -> c MetaValue)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaValue)
-> (MetaValue -> Constr)
-> (MetaValue -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaValue))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue))
-> ((forall b. Data b => b -> b) -> MetaValue -> MetaValue)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r)
-> (forall u. (forall d. Data d => d -> u) -> MetaValue -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MetaValue -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue)
-> Data MetaValue
MetaValue -> Constr
MetaValue -> DataType
(forall b. Data b => b -> b) -> MetaValue -> MetaValue
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) -> MetaValue -> u
forall u. (forall d. Data d => d -> u) -> MetaValue -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaValue
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaValue -> c MetaValue
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaValue)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaValue -> c MetaValue
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MetaValue -> c MetaValue
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaValue
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MetaValue
$ctoConstr :: MetaValue -> Constr
toConstr :: MetaValue -> Constr
$cdataTypeOf :: MetaValue -> DataType
dataTypeOf :: MetaValue -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaValue)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MetaValue)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MetaValue)
$cgmapT :: (forall b. Data b => b -> b) -> MetaValue -> MetaValue
gmapT :: (forall b. Data b => b -> b) -> MetaValue -> MetaValue
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MetaValue -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MetaValue -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MetaValue -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MetaValue -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MetaValue -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MetaValue -> m MetaValue
Data, Typeable, ReadPrec [MetaValue]
ReadPrec MetaValue
Int -> ReadS MetaValue
ReadS [MetaValue]
(Int -> ReadS MetaValue)
-> ReadS [MetaValue]
-> ReadPrec MetaValue
-> ReadPrec [MetaValue]
-> Read MetaValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MetaValue
readsPrec :: Int -> ReadS MetaValue
$creadList :: ReadS [MetaValue]
readList :: ReadS [MetaValue]
$creadPrec :: ReadPrec MetaValue
readPrec :: ReadPrec MetaValue
$creadListPrec :: ReadPrec [MetaValue]
readListPrec :: ReadPrec [MetaValue]
Read, (forall x. MetaValue -> Rep MetaValue x)
-> (forall x. Rep MetaValue x -> MetaValue) -> Generic MetaValue
forall x. Rep MetaValue x -> MetaValue
forall x. MetaValue -> Rep MetaValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MetaValue -> Rep MetaValue x
from :: forall x. MetaValue -> Rep MetaValue x
$cto :: forall x. Rep MetaValue x -> MetaValue
to :: forall x. Rep MetaValue x -> MetaValue
Generic)
instance Plated MetaValue where
plate :: Traversal' MetaValue MetaValue
plate MetaValue -> f MetaValue
f (MetaMap Map Text MetaValue
m) =
Map Text MetaValue -> MetaValue
MetaMap (Map Text MetaValue -> MetaValue)
-> f (Map Text MetaValue) -> f MetaValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MetaValue -> f MetaValue)
-> Map Text MetaValue -> f (Map Text MetaValue)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Map Text a -> f (Map Text b)
traverse MetaValue -> f MetaValue
f Map Text MetaValue
m
plate MetaValue -> f MetaValue
f (MetaList [MetaValue]
x) =
[MetaValue] -> MetaValue
MetaList ([MetaValue] -> MetaValue) -> f [MetaValue] -> f MetaValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (MetaValue -> f MetaValue) -> [MetaValue] -> f [MetaValue]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse MetaValue -> f MetaValue
f [MetaValue]
x
plate MetaValue -> f MetaValue
_ (MetaBool Bool
x) =
MetaValue -> f MetaValue
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> MetaValue
MetaBool Bool
x)
plate MetaValue -> f MetaValue
_ (MetaString Text
x) =
MetaValue -> f MetaValue
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> MetaValue
MetaString Text
x)
plate MetaValue -> f MetaValue
_ (MetaInlines [Inline]
x) =
MetaValue -> f MetaValue
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Inline] -> MetaValue
MetaInlines [Inline]
x)
plate MetaValue -> f MetaValue
_ (MetaBlocks [Block]
x) =
MetaValue -> f MetaValue
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Block] -> MetaValue
MetaBlocks [Block]
x)
class HasMetaValue a where
metaValue ::
Lens' a MetaValue
instance HasMetaValue MetaValue where
metaValue :: Lens' MetaValue MetaValue
metaValue =
(MetaValue -> f MetaValue) -> MetaValue -> f MetaValue
forall a. a -> a
id
instance HasMetaValue D.MetaValue where
metaValue :: Lens' MetaValue MetaValue
metaValue =
AnIso MetaValue MetaValue MetaValue MetaValue
-> Iso MetaValue MetaValue MetaValue MetaValue
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso MetaValue MetaValue MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue
class AsMetaValue a where
_MetaValue ::
Prism' a MetaValue
_MetaMap ::
Prism' a (Map Text MetaValue)
_MetaMap =
p MetaValue (f MetaValue) -> p a (f a)
forall a. AsMetaValue a => Prism' a MetaValue
Prism' a MetaValue
_MetaValue (p MetaValue (f MetaValue) -> p a (f a))
-> (p (Map Text MetaValue) (f (Map Text MetaValue))
-> p MetaValue (f MetaValue))
-> p (Map Text MetaValue) (f (Map Text MetaValue))
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p (Map Text MetaValue) (f (Map Text MetaValue))
-> p MetaValue (f MetaValue)
forall a. AsMetaValue a => Prism' a (Map Text MetaValue)
Prism' MetaValue (Map Text MetaValue)
_MetaMap
_MetaList ::
Prism' a [MetaValue]
_MetaList =
p MetaValue (f MetaValue) -> p a (f a)
forall a. AsMetaValue a => Prism' a MetaValue
Prism' a MetaValue
_MetaValue (p MetaValue (f MetaValue) -> p a (f a))
-> (p [MetaValue] (f [MetaValue]) -> p MetaValue (f MetaValue))
-> p [MetaValue] (f [MetaValue])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [MetaValue] (f [MetaValue]) -> p MetaValue (f MetaValue)
forall a. AsMetaValue a => Prism' a [MetaValue]
Prism' MetaValue [MetaValue]
_MetaList
_MetaBool ::
Prism' a Bool
_MetaBool =
p MetaValue (f MetaValue) -> p a (f a)
forall a. AsMetaValue a => Prism' a MetaValue
Prism' a MetaValue
_MetaValue (p MetaValue (f MetaValue) -> p a (f a))
-> (p Bool (f Bool) -> p MetaValue (f MetaValue))
-> p Bool (f Bool)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Bool (f Bool) -> p MetaValue (f MetaValue)
forall a. AsMetaValue a => Prism' a Bool
Prism' MetaValue Bool
_MetaBool
_MetaString ::
Prism' a Text
_MetaString =
p MetaValue (f MetaValue) -> p a (f a)
forall a. AsMetaValue a => Prism' a MetaValue
Prism' a MetaValue
_MetaValue (p MetaValue (f MetaValue) -> p a (f a))
-> (p Text (f Text) -> p MetaValue (f MetaValue))
-> p Text (f Text)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Text (f Text) -> p MetaValue (f MetaValue)
forall a. AsMetaValue a => Prism' a Text
Prism' MetaValue Text
_MetaString
instance AsMetaValue MetaValue where
_MetaValue :: Prism' MetaValue MetaValue
_MetaValue =
p MetaValue (f MetaValue) -> p MetaValue (f MetaValue)
forall a. a -> a
id
_MetaMap :: Prism' MetaValue (Map Text MetaValue)
_MetaMap =
(Map Text MetaValue -> MetaValue)
-> (MetaValue -> Maybe (Map Text MetaValue))
-> Prism' MetaValue (Map Text MetaValue)
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Map Text MetaValue -> MetaValue
MetaMap
(\case
MetaMap Map Text MetaValue
m -> Map Text MetaValue -> Maybe (Map Text MetaValue)
forall a. a -> Maybe a
Just Map Text MetaValue
m
MetaValue
_ -> Maybe (Map Text MetaValue)
forall a. Maybe a
Nothing)
_MetaList :: Prism' MetaValue [MetaValue]
_MetaList =
([MetaValue] -> MetaValue)
-> (MetaValue -> Maybe [MetaValue]) -> Prism' MetaValue [MetaValue]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[MetaValue] -> MetaValue
MetaList
(\case
MetaList [MetaValue]
m -> [MetaValue] -> Maybe [MetaValue]
forall a. a -> Maybe a
Just [MetaValue]
m
MetaValue
_ -> Maybe [MetaValue]
forall a. Maybe a
Nothing)
_MetaBool :: Prism' MetaValue Bool
_MetaBool =
(Bool -> MetaValue)
-> (MetaValue -> Maybe Bool) -> Prism' MetaValue Bool
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Bool -> MetaValue
MetaBool
(\case
MetaBool Bool
m -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
m
MetaValue
_ -> Maybe Bool
forall a. Maybe a
Nothing)
_MetaString :: Prism' MetaValue Text
_MetaString =
(Text -> MetaValue)
-> (MetaValue -> Maybe Text) -> Prism' MetaValue Text
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Text -> MetaValue
MetaString
(\case
MetaString Text
m -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
m
MetaValue
_ -> Maybe Text
forall a. Maybe a
Nothing)
instance AsInlines MetaValue where
_Inlines :: Prism' MetaValue [Inline]
_Inlines =
([Inline] -> MetaValue)
-> (MetaValue -> Maybe [Inline]) -> Prism' MetaValue [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> MetaValue
MetaInlines
(\case
MetaInlines [Inline]
m -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
m
MetaValue
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
instance AsBlocks MetaValue where
_Blocks :: Prism' MetaValue [Block]
_Blocks =
([Block] -> MetaValue)
-> (MetaValue -> Maybe [Block]) -> Prism' MetaValue [Block]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Block] -> MetaValue
MetaBlocks
(\case
MetaBlocks [Block]
m -> [Block] -> Maybe [Block]
forall a. a -> Maybe a
Just [Block]
m
MetaValue
_ -> Maybe [Block]
forall a. Maybe a
Nothing)
instance AsMetaValue D.MetaValue where
_MetaValue :: Prism' MetaValue MetaValue
_MetaValue =
AnIso MetaValue MetaValue MetaValue MetaValue
-> Iso MetaValue MetaValue MetaValue MetaValue
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso MetaValue MetaValue MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue
isMetaValue ::
Iso'
MetaValue
D.MetaValue
isMetaValue :: Iso' MetaValue MetaValue
isMetaValue =
(MetaValue -> MetaValue)
-> (MetaValue -> MetaValue) -> Iso' MetaValue MetaValue
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
MetaMap Map Text MetaValue
m -> Map Text MetaValue -> MetaValue
D.MetaMap ((MetaValue -> MetaValue)
-> Map Text MetaValue -> Map Text MetaValue
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (Getting MetaValue MetaValue MetaValue -> MetaValue -> MetaValue
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting MetaValue MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue) Map Text MetaValue
m)
MetaList [MetaValue]
m -> [MetaValue] -> MetaValue
D.MetaList ((MetaValue -> MetaValue) -> [MetaValue] -> [MetaValue]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting MetaValue MetaValue MetaValue -> MetaValue -> MetaValue
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting MetaValue MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue) [MetaValue]
m)
MetaBool Bool
b -> Bool -> MetaValue
D.MetaBool Bool
b
MetaString Text
s -> Text -> MetaValue
D.MetaString Text
s
MetaInlines [Inline]
i -> ShortCaption -> MetaValue
D.MetaInlines ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
MetaBlocks [Block]
b -> [Block] -> MetaValue
D.MetaBlocks ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b)
)
(\case
D.MetaMap Map Text MetaValue
m -> Map Text MetaValue -> MetaValue
MetaMap ((MetaValue -> MetaValue)
-> Map Text MetaValue -> Map Text MetaValue
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (AReview MetaValue MetaValue -> MetaValue -> MetaValue
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue) Map Text MetaValue
m)
D.MetaList [MetaValue]
m -> [MetaValue] -> MetaValue
MetaList ((MetaValue -> MetaValue) -> [MetaValue] -> [MetaValue]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview MetaValue MetaValue -> MetaValue -> MetaValue
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue) [MetaValue]
m)
D.MetaBool Bool
b -> Bool -> MetaValue
MetaBool Bool
b
D.MetaString Text
s -> Text -> MetaValue
MetaString Text
s
D.MetaInlines ShortCaption
i -> [Inline] -> MetaValue
MetaInlines ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.MetaBlocks [Block]
b -> [Block] -> MetaValue
MetaBlocks ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b)
)
instance Walkable D.MetaValue MetaValue where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(MetaValue -> m MetaValue) -> MetaValue -> m MetaValue
walkM =
(MetaValue -> m MetaValue) -> MetaValue -> m MetaValue
Iso' MetaValue MetaValue
isMetaValue
query :: forall c. Monoid c => (MetaValue -> c) -> MetaValue -> c
query MetaValue -> c
f =
MetaValue -> c
f (MetaValue -> c) -> (MetaValue -> MetaValue) -> MetaValue -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting MetaValue MetaValue MetaValue -> MetaValue -> MetaValue
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting MetaValue MetaValue MetaValue
Iso' MetaValue MetaValue
isMetaValue
data QuoteType =
SingleQuote
| DoubleQuote
deriving (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, 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, 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, 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, Typeable, ReadPrec [QuoteType]
ReadPrec QuoteType
Int -> ReadS QuoteType
ReadS [QuoteType]
(Int -> ReadS QuoteType)
-> ReadS [QuoteType]
-> ReadPrec QuoteType
-> ReadPrec [QuoteType]
-> Read QuoteType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS QuoteType
readsPrec :: Int -> ReadS QuoteType
$creadList :: ReadS [QuoteType]
readList :: ReadS [QuoteType]
$creadPrec :: ReadPrec QuoteType
readPrec :: ReadPrec QuoteType
$creadListPrec :: ReadPrec [QuoteType]
readListPrec :: ReadPrec [QuoteType]
Read, (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)
class HasQuoteType a where
quoteType ::
Lens' a QuoteType
instance HasQuoteType QuoteType where
quoteType :: Lens' QuoteType QuoteType
quoteType =
(QuoteType -> f QuoteType) -> QuoteType -> f QuoteType
forall a. a -> a
id
instance HasQuoteType D.QuoteType where
quoteType :: Lens' QuoteType QuoteType
quoteType =
AnIso QuoteType QuoteType QuoteType QuoteType
-> Iso QuoteType QuoteType QuoteType QuoteType
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso QuoteType QuoteType QuoteType QuoteType
Iso' QuoteType QuoteType
isQuoteType
class AsQuoteType a where
_QuoteType ::
Prism' a QuoteType
_SingleQuote ::
Prism' a ()
_SingleQuote =
p QuoteType (f QuoteType) -> p a (f a)
forall a. AsQuoteType a => Prism' a QuoteType
Prism' a QuoteType
_QuoteType (p QuoteType (f QuoteType) -> p a (f a))
-> (p () (f ()) -> p QuoteType (f QuoteType))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p QuoteType (f QuoteType)
forall a. AsQuoteType a => Prism' a ()
Prism' QuoteType ()
_SingleQuote
_DoubleQuote ::
Prism' a ()
_DoubleQuote =
p QuoteType (f QuoteType) -> p a (f a)
forall a. AsQuoteType a => Prism' a QuoteType
Prism' a QuoteType
_QuoteType (p QuoteType (f QuoteType) -> p a (f a))
-> (p () (f ()) -> p QuoteType (f QuoteType))
-> p () (f ())
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p QuoteType (f QuoteType)
forall a. AsQuoteType a => Prism' a ()
Prism' QuoteType ()
_DoubleQuote
instance AsQuoteType QuoteType where
_QuoteType :: Prism' QuoteType QuoteType
_QuoteType =
p QuoteType (f QuoteType) -> p QuoteType (f QuoteType)
forall a. a -> a
id
_SingleQuote :: Prism' QuoteType ()
_SingleQuote =
(() -> QuoteType) -> (QuoteType -> Maybe ()) -> Prism' QuoteType ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> QuoteType
SingleQuote)
(\case
QuoteType
SingleQuote -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
QuoteType
_ -> Maybe ()
forall a. Maybe a
Nothing)
_DoubleQuote :: Prism' QuoteType ()
_DoubleQuote =
(() -> QuoteType) -> (QuoteType -> Maybe ()) -> Prism' QuoteType ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> QuoteType
DoubleQuote)
(\case
QuoteType
DoubleQuote -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
QuoteType
_ -> Maybe ()
forall a. Maybe a
Nothing)
instance AsQuoteType D.QuoteType where
_QuoteType :: Prism' QuoteType QuoteType
_QuoteType =
AnIso QuoteType QuoteType QuoteType QuoteType
-> Iso QuoteType QuoteType QuoteType QuoteType
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso QuoteType QuoteType QuoteType QuoteType
Iso' QuoteType QuoteType
isQuoteType
isQuoteType ::
Iso'
QuoteType
D.QuoteType
isQuoteType :: Iso' QuoteType QuoteType
isQuoteType =
(QuoteType -> QuoteType)
-> (QuoteType -> QuoteType) -> Iso' QuoteType QuoteType
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
QuoteType
SingleQuote -> QuoteType
D.SingleQuote
QuoteType
DoubleQuote -> QuoteType
D.DoubleQuote
)
(\case
QuoteType
D.SingleQuote -> QuoteType
SingleQuote
QuoteType
D.DoubleQuote -> QuoteType
DoubleQuote
)
instance Walkable D.QuoteType QuoteType where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(QuoteType -> m QuoteType) -> QuoteType -> m QuoteType
walkM =
(QuoteType -> m QuoteType) -> QuoteType -> m QuoteType
Iso' QuoteType QuoteType
isQuoteType
query :: forall c. Monoid c => (QuoteType -> c) -> QuoteType -> c
query QuoteType -> c
f =
QuoteType -> c
f (QuoteType -> c) -> (QuoteType -> QuoteType) -> QuoteType -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting QuoteType QuoteType QuoteType -> QuoteType -> QuoteType
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting QuoteType QuoteType QuoteType
Iso' QuoteType QuoteType
isQuoteType
newtype ShortCaption =
ShortCaption [Inline]
deriving (ShortCaption -> ShortCaption -> Bool
(ShortCaption -> ShortCaption -> Bool)
-> (ShortCaption -> ShortCaption -> Bool) -> Eq ShortCaption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShortCaption -> ShortCaption -> Bool
== :: ShortCaption -> ShortCaption -> Bool
$c/= :: ShortCaption -> ShortCaption -> Bool
/= :: ShortCaption -> ShortCaption -> Bool
Eq, Eq ShortCaption
Eq ShortCaption =>
(ShortCaption -> ShortCaption -> Ordering)
-> (ShortCaption -> ShortCaption -> Bool)
-> (ShortCaption -> ShortCaption -> Bool)
-> (ShortCaption -> ShortCaption -> Bool)
-> (ShortCaption -> ShortCaption -> Bool)
-> (ShortCaption -> ShortCaption -> ShortCaption)
-> (ShortCaption -> ShortCaption -> ShortCaption)
-> Ord ShortCaption
ShortCaption -> ShortCaption -> Bool
ShortCaption -> ShortCaption -> Ordering
ShortCaption -> ShortCaption -> ShortCaption
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 :: ShortCaption -> ShortCaption -> Ordering
compare :: ShortCaption -> ShortCaption -> Ordering
$c< :: ShortCaption -> ShortCaption -> Bool
< :: ShortCaption -> ShortCaption -> Bool
$c<= :: ShortCaption -> ShortCaption -> Bool
<= :: ShortCaption -> ShortCaption -> Bool
$c> :: ShortCaption -> ShortCaption -> Bool
> :: ShortCaption -> ShortCaption -> Bool
$c>= :: ShortCaption -> ShortCaption -> Bool
>= :: ShortCaption -> ShortCaption -> Bool
$cmax :: ShortCaption -> ShortCaption -> ShortCaption
max :: ShortCaption -> ShortCaption -> ShortCaption
$cmin :: ShortCaption -> ShortCaption -> ShortCaption
min :: ShortCaption -> ShortCaption -> ShortCaption
Ord, Int -> ShortCaption -> ShowS
[ShortCaption] -> ShowS
ShortCaption -> String
(Int -> ShortCaption -> ShowS)
-> (ShortCaption -> String)
-> ([ShortCaption] -> ShowS)
-> Show ShortCaption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ShortCaption -> ShowS
showsPrec :: Int -> ShortCaption -> ShowS
$cshow :: ShortCaption -> String
show :: ShortCaption -> String
$cshowList :: [ShortCaption] -> ShowS
showList :: [ShortCaption] -> ShowS
Show, Typeable ShortCaption
Typeable ShortCaption =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortCaption -> c ShortCaption)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortCaption)
-> (ShortCaption -> Constr)
-> (ShortCaption -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortCaption))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortCaption))
-> ((forall b. Data b => b -> b) -> ShortCaption -> ShortCaption)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r)
-> (forall u. (forall d. Data d => d -> u) -> ShortCaption -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ShortCaption -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption)
-> Data ShortCaption
ShortCaption -> Constr
ShortCaption -> DataType
(forall b. Data b => b -> b) -> ShortCaption -> ShortCaption
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) -> ShortCaption -> u
forall u. (forall d. Data d => d -> u) -> ShortCaption -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortCaption
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortCaption -> c ShortCaption
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortCaption)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortCaption)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortCaption -> c ShortCaption
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortCaption -> c ShortCaption
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortCaption
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortCaption
$ctoConstr :: ShortCaption -> Constr
toConstr :: ShortCaption -> Constr
$cdataTypeOf :: ShortCaption -> DataType
dataTypeOf :: ShortCaption -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortCaption)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ShortCaption)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortCaption)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ShortCaption)
$cgmapT :: (forall b. Data b => b -> b) -> ShortCaption -> ShortCaption
gmapT :: (forall b. Data b => b -> b) -> ShortCaption -> ShortCaption
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ShortCaption -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ShortCaption -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ShortCaption -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ShortCaption -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ShortCaption -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ShortCaption -> m ShortCaption
Data, Typeable, ReadPrec [ShortCaption]
ReadPrec ShortCaption
Int -> ReadS ShortCaption
ReadS [ShortCaption]
(Int -> ReadS ShortCaption)
-> ReadS [ShortCaption]
-> ReadPrec ShortCaption
-> ReadPrec [ShortCaption]
-> Read ShortCaption
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ShortCaption
readsPrec :: Int -> ReadS ShortCaption
$creadList :: ReadS [ShortCaption]
readList :: ReadS [ShortCaption]
$creadPrec :: ReadPrec ShortCaption
readPrec :: ReadPrec ShortCaption
$creadListPrec :: ReadPrec [ShortCaption]
readListPrec :: ReadPrec [ShortCaption]
Read, (forall x. ShortCaption -> Rep ShortCaption x)
-> (forall x. Rep ShortCaption x -> ShortCaption)
-> Generic ShortCaption
forall x. Rep ShortCaption x -> ShortCaption
forall x. ShortCaption -> Rep ShortCaption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ShortCaption -> Rep ShortCaption x
from :: forall x. ShortCaption -> Rep ShortCaption x
$cto :: forall x. Rep ShortCaption x -> ShortCaption
to :: forall x. Rep ShortCaption x -> ShortCaption
Generic)
instance Semigroup ShortCaption where
ShortCaption [Inline]
x <> :: ShortCaption -> ShortCaption -> ShortCaption
<> ShortCaption [Inline]
y =
[Inline] -> ShortCaption
ShortCaption ([Inline]
x [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
y)
instance Monoid ShortCaption where
mempty :: ShortCaption
mempty =
[Inline] -> ShortCaption
ShortCaption [Inline]
forall a. Monoid a => a
mempty
instance (ShortCaption ~ t) => Rewrapped ShortCaption t
instance Wrapped ShortCaption where
type Unwrapped ShortCaption =
[Inline]
_Wrapped' :: Iso' ShortCaption (Unwrapped ShortCaption)
_Wrapped' =
(ShortCaption -> [Inline])
-> ([Inline] -> ShortCaption)
-> Iso ShortCaption ShortCaption [Inline] [Inline]
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (\(ShortCaption [Inline]
x) -> [Inline]
x) [Inline] -> ShortCaption
ShortCaption
class HasShortCaption a where
shortCaption ::
Lens' a ShortCaption
instance HasShortCaption ShortCaption where
shortCaption :: Lens' ShortCaption ShortCaption
shortCaption =
(ShortCaption -> f ShortCaption) -> ShortCaption -> f ShortCaption
forall a. a -> a
id
instance HasShortCaption D.ShortCaption where
shortCaption :: Lens' ShortCaption ShortCaption
shortCaption =
AnIso ShortCaption ShortCaption ShortCaption ShortCaption
-> Iso ShortCaption ShortCaption ShortCaption ShortCaption
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ShortCaption ShortCaption ShortCaption ShortCaption
Iso' ShortCaption ShortCaption
isShortCaption
class AsShortCaption a where
_ShortCaption ::
Prism' a ShortCaption
instance AsShortCaption ShortCaption where
_ShortCaption :: Prism' ShortCaption ShortCaption
_ShortCaption =
p ShortCaption (f ShortCaption) -> p ShortCaption (f ShortCaption)
forall a. a -> a
id
instance AsShortCaption D.ShortCaption where
_ShortCaption :: Prism' ShortCaption ShortCaption
_ShortCaption =
AnIso ShortCaption ShortCaption ShortCaption ShortCaption
-> Iso ShortCaption ShortCaption ShortCaption ShortCaption
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso ShortCaption ShortCaption ShortCaption ShortCaption
Iso' ShortCaption ShortCaption
isShortCaption
instance HasInlines ShortCaption where
inlines :: Lens' ShortCaption [Inline]
inlines =
([Inline] -> f [Inline]) -> ShortCaption -> f ShortCaption
(Unwrapped ShortCaption -> f (Unwrapped ShortCaption))
-> ShortCaption -> f ShortCaption
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso' ShortCaption (Unwrapped ShortCaption)
_Wrapped
instance AsInlines ShortCaption where
_Inlines :: Prism' ShortCaption [Inline]
_Inlines =
p [Inline] (f [Inline]) -> p ShortCaption (f ShortCaption)
p (Unwrapped ShortCaption) (f (Unwrapped ShortCaption))
-> p ShortCaption (f ShortCaption)
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso' ShortCaption (Unwrapped ShortCaption)
_Wrapped
isShortCaption ::
Iso'
ShortCaption
D.ShortCaption
isShortCaption :: Iso' ShortCaption ShortCaption
isShortCaption =
(ShortCaption -> ShortCaption)
-> (ShortCaption -> ShortCaption) -> Iso' ShortCaption ShortCaption
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(ShortCaption [Inline]
x) -> (Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
x)
([Inline] -> ShortCaption
ShortCaption ([Inline] -> ShortCaption)
-> (ShortCaption -> [Inline]) -> ShortCaption -> ShortCaption
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline))
instance Walkable D.ShortCaption ShortCaption where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(ShortCaption -> m ShortCaption) -> ShortCaption -> m ShortCaption
walkM =
(ShortCaption -> m ShortCaption) -> ShortCaption -> m ShortCaption
Iso' ShortCaption ShortCaption
isShortCaption
query :: forall c. Monoid c => (ShortCaption -> c) -> ShortCaption -> c
query ShortCaption -> c
f =
ShortCaption -> c
f (ShortCaption -> c)
-> (ShortCaption -> ShortCaption) -> ShortCaption -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting ShortCaption ShortCaption ShortCaption
-> ShortCaption -> ShortCaption
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ShortCaption ShortCaption ShortCaption
Iso' ShortCaption ShortCaption
isShortCaption
data Target =
Target
Text
Text
deriving (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, 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, 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, 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, Typeable, ReadPrec [Target]
ReadPrec Target
Int -> ReadS Target
ReadS [Target]
(Int -> ReadS Target)
-> ReadS [Target]
-> ReadPrec Target
-> ReadPrec [Target]
-> Read Target
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Target
readsPrec :: Int -> ReadS Target
$creadList :: ReadS [Target]
readList :: ReadS [Target]
$creadPrec :: ReadPrec Target
readPrec :: ReadPrec Target
$creadListPrec :: ReadPrec [Target]
readListPrec :: ReadPrec [Target]
Read, (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)
instance Semigroup Target where
Target Text
t1 Text
t2 <> :: Target -> Target -> Target
<> Target Text
u1 Text
u2 =
Text -> Text -> Target
Target (Text
t1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
u1) (Text
t2 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
u2)
instance Monoid Target where
mempty :: Target
mempty =
Text -> Text -> Target
Target Text
forall a. Monoid a => a
mempty Text
forall a. Monoid a => a
mempty
class HasTarget a where
target ::
Lens' a Target
targetURL ::
Lens' a Text
targetURL =
(Target -> f Target) -> a -> f a
forall a. HasTarget a => Lens' a Target
Lens' a Target
target ((Target -> f Target) -> a -> f a)
-> ((Text -> f Text) -> Target -> f Target)
-> (Text -> f Text)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> f Text) -> Target -> f Target
forall a. HasTarget a => Lens' a Text
Lens' Target Text
targetURL
targetTitle ::
Lens' a Text
targetTitle =
(Target -> f Target) -> a -> f a
forall a. HasTarget a => Lens' a Target
Lens' a Target
target ((Target -> f Target) -> a -> f a)
-> ((Text -> f Text) -> Target -> f Target)
-> (Text -> f Text)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> f Text) -> Target -> f Target
forall a. HasTarget a => Lens' a Text
Lens' Target Text
targetTitle
instance HasTarget Target where
target :: Lens' Target Target
target =
(Target -> f Target) -> Target -> f Target
forall a. a -> a
id
targetURL :: Lens' Target Text
targetURL Text -> f Text
f (Target Text
u Text
t) =
(Text -> Target) -> f Text -> f Target
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text -> Target
`Target` Text
t) (Text -> f Text
f Text
u)
targetTitle :: Lens' Target Text
targetTitle Text -> f Text
f (Target Text
u Text
t) =
(Text -> Target) -> f Text -> f Target
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text -> Target
Target Text
u) (Text -> f Text
f Text
t)
instance HasTarget D.Target where
target :: Lens' (Text, Text) Target
target =
AnIso Target Target (Text, Text) (Text, Text)
-> Iso (Text, Text) (Text, Text) Target Target
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Target Target (Text, Text) (Text, Text)
Iso' Target (Text, Text)
isTarget
class AsTarget a where
_Target ::
Prism' a Target
instance AsTarget Target where
_Target :: Prism' Target Target
_Target =
p Target (f Target) -> p Target (f Target)
forall a. a -> a
id
instance AsTarget D.Target where
_Target :: Prism' (Text, Text) Target
_Target =
AnIso Target Target (Text, Text) (Text, Text)
-> Iso (Text, Text) (Text, Text) Target Target
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Target Target (Text, Text) (Text, Text)
Iso' Target (Text, Text)
isTarget
isTarget ::
Iso'
Target
D.Target
isTarget :: Iso' Target (Text, Text)
isTarget =
(Target -> (Text, Text))
-> ((Text, Text) -> Target) -> Iso' Target (Text, Text)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Target Text
t1 Text
t2) -> (Text
t1, Text
t2))
(\(Text
t1, Text
t2) -> Text -> Text -> Target
Target Text
t1 Text
t2)
instance Walkable D.Target Target where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
((Text, Text) -> m (Text, Text)) -> Target -> m Target
walkM =
((Text, Text) -> m (Text, Text)) -> Target -> m Target
Iso' Target (Text, Text)
isTarget
query :: forall c. Monoid c => ((Text, Text) -> c) -> Target -> c
query (Text, Text) -> c
f =
(Text, Text) -> c
f ((Text, Text) -> c) -> (Target -> (Text, Text)) -> Target -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (Text, Text) Target (Text, Text) -> Target -> (Text, Text)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Text, Text) Target (Text, Text)
Iso' Target (Text, Text)
isTarget
data Link =
Link
Attr
[Inline]
Target
deriving (Link -> Link -> Bool
(Link -> Link -> Bool) -> (Link -> Link -> Bool) -> Eq Link
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Link -> Link -> Bool
== :: Link -> Link -> Bool
$c/= :: Link -> Link -> Bool
/= :: Link -> Link -> Bool
Eq, Eq Link
Eq Link =>
(Link -> Link -> Ordering)
-> (Link -> Link -> Bool)
-> (Link -> Link -> Bool)
-> (Link -> Link -> Bool)
-> (Link -> Link -> Bool)
-> (Link -> Link -> Link)
-> (Link -> Link -> Link)
-> Ord Link
Link -> Link -> Bool
Link -> Link -> Ordering
Link -> Link -> Link
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 :: Link -> Link -> Ordering
compare :: Link -> Link -> Ordering
$c< :: Link -> Link -> Bool
< :: Link -> Link -> Bool
$c<= :: Link -> Link -> Bool
<= :: Link -> Link -> Bool
$c> :: Link -> Link -> Bool
> :: Link -> Link -> Bool
$c>= :: Link -> Link -> Bool
>= :: Link -> Link -> Bool
$cmax :: Link -> Link -> Link
max :: Link -> Link -> Link
$cmin :: Link -> Link -> Link
min :: Link -> Link -> Link
Ord, Int -> Link -> ShowS
[Link] -> ShowS
Link -> String
(Int -> Link -> ShowS)
-> (Link -> String) -> ([Link] -> ShowS) -> Show Link
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Link -> ShowS
showsPrec :: Int -> Link -> ShowS
$cshow :: Link -> String
show :: Link -> String
$cshowList :: [Link] -> ShowS
showList :: [Link] -> ShowS
Show, Typeable Link
Typeable Link =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link)
-> (Link -> Constr)
-> (Link -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link))
-> ((forall b. Data b => b -> b) -> Link -> Link)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r)
-> (forall u. (forall d. Data d => d -> u) -> Link -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Link -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Link -> m Link)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link)
-> Data Link
Link -> Constr
Link -> DataType
(forall b. Data b => b -> b) -> Link -> Link
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) -> Link -> u
forall u. (forall d. Data d => d -> u) -> Link -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Link -> m Link
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Link -> c Link
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Link
$ctoConstr :: Link -> Constr
toConstr :: Link -> Constr
$cdataTypeOf :: Link -> DataType
dataTypeOf :: Link -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Link)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Link)
$cgmapT :: (forall b. Data b => b -> b) -> Link -> Link
gmapT :: (forall b. Data b => b -> b) -> Link -> Link
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Link -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Link -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Link -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Link -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Link -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Link -> m Link
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Link -> m Link
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Link -> m Link
Data, Typeable, ReadPrec [Link]
ReadPrec Link
Int -> ReadS Link
ReadS [Link]
(Int -> ReadS Link)
-> ReadS [Link] -> ReadPrec Link -> ReadPrec [Link] -> Read Link
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Link
readsPrec :: Int -> ReadS Link
$creadList :: ReadS [Link]
readList :: ReadS [Link]
$creadPrec :: ReadPrec Link
readPrec :: ReadPrec Link
$creadListPrec :: ReadPrec [Link]
readListPrec :: ReadPrec [Link]
Read, (forall x. Link -> Rep Link x)
-> (forall x. Rep Link x -> Link) -> Generic Link
forall x. Rep Link x -> Link
forall x. Link -> Rep Link x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Link -> Rep Link x
from :: forall x. Link -> Rep Link x
$cto :: forall x. Rep Link x -> Link
to :: forall x. Rep Link x -> Link
Generic)
instance Semigroup Link where
Link Attr
a1 [Inline]
c1 Target
i1 <> :: Link -> Link -> Link
<> Link Attr
a2 [Inline]
c2 Target
i2 =
Attr -> [Inline] -> Target -> Link
Link (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) ([Inline]
c1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
c2) (Target
i1 Target -> Target -> Target
forall a. Semigroup a => a -> a -> a
<> Target
i2)
instance Monoid Link where
mempty :: Link
mempty =
Attr -> [Inline] -> Target -> Link
Link Attr
forall a. Monoid a => a
mempty [Inline]
forall a. Monoid a => a
mempty Target
forall a. Monoid a => a
mempty
class HasLink a where
link ::
Lens' a Link
instance HasLink Link where
link :: Lens' Link Link
link =
(Link -> f Link) -> Link -> f Link
forall a. a -> a
id
instance HasInlines Link where
inlines :: Lens' Link [Inline]
inlines [Inline] -> f [Inline]
f (Link Attr
a [Inline]
i Target
t) =
([Inline] -> Link) -> f [Inline] -> f Link
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Inline]
i' -> Attr -> [Inline] -> Target -> Link
Link Attr
a [Inline]
i' Target
t) ([Inline] -> f [Inline]
f [Inline]
i)
instance HasAttr Link where
attr :: Lens' Link Attr
attr Attr -> f Attr
f (Link Attr
a [Inline]
i Target
t) =
(Attr -> Link) -> f Attr -> f Link
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Attr -> [Inline] -> Target -> Link
Link Attr
a' [Inline]
i Target
t) (Attr -> f Attr
f Attr
a)
instance HasTarget Link where
target :: Lens' Link Target
target Target -> f Target
f (Link Attr
a [Inline]
i Target
t) =
(Target -> Link) -> f Target -> f Link
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Inline] -> Target -> Link
Link Attr
a [Inline]
i) (Target -> f Target
f Target
t)
class AsLink a where
_Link ::
Prism' a Link
instance AsLink Link where
_Link :: Prism' Link Link
_Link =
p Link (f Link) -> p Link (f Link)
forall a. a -> a
id
instance AsLink Inline where
_Link :: Prism' Inline Link
_Link =
(Link -> Inline) -> (Inline -> Maybe Link) -> Prism' Inline Link
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Link -> Inline
LinkInline
(\case
LinkInline Link
x -> Link -> Maybe Link
forall a. a -> Maybe a
Just Link
x
Inline
_ -> Maybe Link
forall a. Maybe a
Nothing)
instance AsLink D.Inline where
_Link :: Prism' Inline Link
_Link =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Link (f Link) -> p Inline (f Inline))
-> p Link (f Link)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Link (f Link) -> p Inline (f Inline)
forall a. AsLink a => Prism' a Link
Prism' Inline Link
_Link
data Image =
Image
Attr
[Inline]
Target
deriving (Image -> Image -> Bool
(Image -> Image -> Bool) -> (Image -> Image -> Bool) -> Eq Image
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
/= :: Image -> Image -> Bool
Eq, Eq Image
Eq Image =>
(Image -> Image -> Ordering)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Image)
-> (Image -> Image -> Image)
-> Ord Image
Image -> Image -> Bool
Image -> Image -> Ordering
Image -> Image -> Image
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 :: Image -> Image -> Ordering
compare :: Image -> Image -> Ordering
$c< :: Image -> Image -> Bool
< :: Image -> Image -> Bool
$c<= :: Image -> Image -> Bool
<= :: Image -> Image -> Bool
$c> :: Image -> Image -> Bool
> :: Image -> Image -> Bool
$c>= :: Image -> Image -> Bool
>= :: Image -> Image -> Bool
$cmax :: Image -> Image -> Image
max :: Image -> Image -> Image
$cmin :: Image -> Image -> Image
min :: Image -> Image -> Image
Ord, Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
(Int -> Image -> ShowS)
-> (Image -> String) -> ([Image] -> ShowS) -> Show Image
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Image -> ShowS
showsPrec :: Int -> Image -> ShowS
$cshow :: Image -> String
show :: Image -> String
$cshowList :: [Image] -> ShowS
showList :: [Image] -> ShowS
Show, Typeable Image
Typeable Image =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image)
-> (Image -> Constr)
-> (Image -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image))
-> ((forall b. Data b => b -> b) -> Image -> Image)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r)
-> (forall u. (forall d. Data d => d -> u) -> Image -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Image -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image)
-> Data Image
Image -> Constr
Image -> DataType
(forall b. Data b => b -> b) -> Image -> Image
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) -> Image -> u
forall u. (forall d. Data d => d -> u) -> Image -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Image -> c Image
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Image
$ctoConstr :: Image -> Constr
toConstr :: Image -> Constr
$cdataTypeOf :: Image -> DataType
dataTypeOf :: Image -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Image)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image)
$cgmapT :: (forall b. Data b => b -> b) -> Image -> Image
gmapT :: (forall b. Data b => b -> b) -> Image -> Image
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Image -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Image -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Image -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Image -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Image -> m Image
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Image -> m Image
Data, Typeable, ReadPrec [Image]
ReadPrec Image
Int -> ReadS Image
ReadS [Image]
(Int -> ReadS Image)
-> ReadS [Image]
-> ReadPrec Image
-> ReadPrec [Image]
-> Read Image
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Image
readsPrec :: Int -> ReadS Image
$creadList :: ReadS [Image]
readList :: ReadS [Image]
$creadPrec :: ReadPrec Image
readPrec :: ReadPrec Image
$creadListPrec :: ReadPrec [Image]
readListPrec :: ReadPrec [Image]
Read, (forall x. Image -> Rep Image x)
-> (forall x. Rep Image x -> Image) -> Generic Image
forall x. Rep Image x -> Image
forall x. Image -> Rep Image x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Image -> Rep Image x
from :: forall x. Image -> Rep Image x
$cto :: forall x. Rep Image x -> Image
to :: forall x. Rep Image x -> Image
Generic)
instance Semigroup Image where
Image Attr
a1 [Inline]
c1 Target
i1 <> :: Image -> Image -> Image
<> Image Attr
a2 [Inline]
c2 Target
i2 =
Attr -> [Inline] -> Target -> Image
Image (Attr
a1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
a2) ([Inline]
c1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
c2) (Target
i1 Target -> Target -> Target
forall a. Semigroup a => a -> a -> a
<> Target
i2)
instance Monoid Image where
mempty :: Image
mempty =
Attr -> [Inline] -> Target -> Image
Image Attr
forall a. Monoid a => a
mempty [Inline]
forall a. Monoid a => a
mempty Target
forall a. Monoid a => a
mempty
class HasImage a where
image ::
Lens' a Image
instance HasImage Image where
image :: Lens' Image Image
image =
(Image -> f Image) -> Image -> f Image
forall a. a -> a
id
instance HasInlines Image where
inlines :: Lens' Image [Inline]
inlines [Inline] -> f [Inline]
f (Image Attr
a [Inline]
i Target
t) =
([Inline] -> Image) -> f [Inline] -> f Image
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Inline]
i' -> Attr -> [Inline] -> Target -> Image
Image Attr
a [Inline]
i' Target
t) ([Inline] -> f [Inline]
f [Inline]
i)
instance HasAttr Image where
attr :: Lens' Image Attr
attr Attr -> f Attr
f (Image Attr
a [Inline]
i Target
t) =
(Attr -> Image) -> f Attr -> f Image
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Attr
a' -> Attr -> [Inline] -> Target -> Image
Image Attr
a' [Inline]
i Target
t) (Attr -> f Attr
f Attr
a)
instance HasTarget Image where
target :: Lens' Image Target
target Target -> f Target
f (Image Attr
a [Inline]
i Target
t) =
(Target -> Image) -> f Target -> f Image
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Inline] -> Target -> Image
Image Attr
a [Inline]
i) (Target -> f Target
f Target
t)
class AsImage a where
_Image ::
Prism' a Image
instance AsImage Image where
_Image :: Prism' Image Image
_Image =
p Image (f Image) -> p Image (f Image)
forall a. a -> a
id
instance AsImage Inline where
_Image :: Prism' Inline Image
_Image =
(Image -> Inline) -> (Inline -> Maybe Image) -> Prism' Inline Image
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Image -> Inline
ImageInline
(\case
ImageInline Image
x -> Image -> Maybe Image
forall a. a -> Maybe a
Just Image
x
Inline
_ -> Maybe Image
forall a. Maybe a
Nothing)
instance AsImage D.Inline where
_Image :: Prism' Inline Image
_Image =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Image (f Image) -> p Inline (f Inline))
-> p Image (f Image)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Image (f Image) -> p Inline (f Inline)
forall a. AsImage a => Prism' a Image
Prism' Inline Image
_Image
data Span =
Span
Attr
[Inline]
deriving (Span -> Span -> Bool
(Span -> Span -> Bool) -> (Span -> Span -> Bool) -> Eq Span
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Span -> Span -> Bool
== :: Span -> Span -> Bool
$c/= :: Span -> Span -> Bool
/= :: Span -> Span -> Bool
Eq, Eq Span
Eq Span =>
(Span -> Span -> Ordering)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Bool)
-> (Span -> Span -> Span)
-> (Span -> Span -> Span)
-> Ord Span
Span -> Span -> Bool
Span -> Span -> Ordering
Span -> Span -> Span
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 :: Span -> Span -> Ordering
compare :: Span -> Span -> Ordering
$c< :: Span -> Span -> Bool
< :: Span -> Span -> Bool
$c<= :: Span -> Span -> Bool
<= :: Span -> Span -> Bool
$c> :: Span -> Span -> Bool
> :: Span -> Span -> Bool
$c>= :: Span -> Span -> Bool
>= :: Span -> Span -> Bool
$cmax :: Span -> Span -> Span
max :: Span -> Span -> Span
$cmin :: Span -> Span -> Span
min :: Span -> Span -> Span
Ord, Int -> Span -> ShowS
[Span] -> ShowS
Span -> String
(Int -> Span -> ShowS)
-> (Span -> String) -> ([Span] -> ShowS) -> Show Span
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Span -> ShowS
showsPrec :: Int -> Span -> ShowS
$cshow :: Span -> String
show :: Span -> String
$cshowList :: [Span] -> ShowS
showList :: [Span] -> ShowS
Show, Typeable Span
Typeable Span =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Span -> c Span)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Span)
-> (Span -> Constr)
-> (Span -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Span))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span))
-> ((forall b. Data b => b -> b) -> Span -> Span)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r)
-> (forall u. (forall d. Data d => d -> u) -> Span -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Span -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Span -> m Span)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span)
-> Data Span
Span -> Constr
Span -> DataType
(forall b. Data b => b -> b) -> Span -> Span
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) -> Span -> u
forall u. (forall d. Data d => d -> u) -> Span -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Span -> m Span
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Span
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Span -> c Span
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Span)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Span -> c Span
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Span -> c Span
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Span
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Span
$ctoConstr :: Span -> Constr
toConstr :: Span -> Constr
$cdataTypeOf :: Span -> DataType
dataTypeOf :: Span -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Span)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Span)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Span)
$cgmapT :: (forall b. Data b => b -> b) -> Span -> Span
gmapT :: (forall b. Data b => b -> b) -> Span -> Span
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Span -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Span -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Span -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Span -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Span -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Span -> m Span
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Span -> m Span
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Span -> m Span
Data, Typeable, ReadPrec [Span]
ReadPrec Span
Int -> ReadS Span
ReadS [Span]
(Int -> ReadS Span)
-> ReadS [Span] -> ReadPrec Span -> ReadPrec [Span] -> Read Span
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Span
readsPrec :: Int -> ReadS Span
$creadList :: ReadS [Span]
readList :: ReadS [Span]
$creadPrec :: ReadPrec Span
readPrec :: ReadPrec Span
$creadListPrec :: ReadPrec [Span]
readListPrec :: ReadPrec [Span]
Read, (forall x. Span -> Rep Span x)
-> (forall x. Rep Span x -> Span) -> Generic Span
forall x. Rep Span x -> Span
forall x. Span -> Rep Span x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Span -> Rep Span x
from :: forall x. Span -> Rep Span x
$cto :: forall x. Rep Span x -> Span
to :: forall x. Rep Span x -> Span
Generic)
instance Semigroup Span where
Span Attr
c1 [Inline]
i1 <> :: Span -> Span -> Span
<> Span Attr
c2 [Inline]
i2 =
Attr -> [Inline] -> Span
Span (Attr
c1 Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> Attr
c2) ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
instance Monoid Span where
mempty :: Span
mempty =
Attr -> [Inline] -> Span
Span Attr
forall a. Monoid a => a
mempty [Inline]
forall a. Monoid a => a
mempty
class HasSpan a where
span ::
Lens' a Span
instance HasSpan Span where
span :: Lens' Span Span
span =
(Span -> f Span) -> Span -> f Span
forall a. a -> a
id
instance HasSpan Link where
span :: Lens' Link Span
span Span -> f Span
f (Link Attr
a [Inline]
i Target
t) =
(Span -> Link) -> f Span -> f Link
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Span Attr
a' [Inline]
i') -> Attr -> [Inline] -> Target -> Link
Link Attr
a' [Inline]
i' Target
t) (Span -> f Span
f (Attr -> [Inline] -> Span
Span Attr
a [Inline]
i))
instance HasSpan Image where
span :: Lens' Image Span
span Span -> f Span
f (Image Attr
a [Inline]
i Target
t) =
(Span -> Image) -> f Span -> f Image
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Span Attr
a' [Inline]
i') -> Attr -> [Inline] -> Target -> Image
Image Attr
a' [Inline]
i' Target
t) (Span -> f Span
f (Attr -> [Inline] -> Span
Span Attr
a [Inline]
i))
instance HasInlines Span where
inlines :: Lens' Span [Inline]
inlines [Inline] -> f [Inline]
f (Span Attr
a [Inline]
i) =
([Inline] -> Span) -> f [Inline] -> f Span
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Inline] -> Span
Span Attr
a) ([Inline] -> f [Inline]
f [Inline]
i)
instance HasAttr Span where
attr :: Lens' Span Attr
attr Attr -> f Attr
f (Span Attr
a [Inline]
i) =
(Attr -> Span) -> f Attr -> f Span
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Inline] -> Span
`Span` [Inline]
i) (Attr -> f Attr
f Attr
a)
class AsSpan a where
_Span ::
Prism' a Span
instance AsSpan Span where
_Span :: Prism' Span Span
_Span =
p Span (f Span) -> p Span (f Span)
forall a. a -> a
id
instance AsSpan Inline where
_Span :: Prism' Inline Span
_Span =
(Span -> Inline) -> (Inline -> Maybe Span) -> Prism' Inline Span
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Span -> Inline
SpanInline
(\case
SpanInline Span
x -> Span -> Maybe Span
forall a. a -> Maybe a
Just Span
x
Inline
_ -> Maybe Span
forall a. Maybe a
Nothing)
instance AsSpan D.Inline where
_Span :: Prism' Inline Span
_Span =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Span (f Span) -> p Inline (f Inline))
-> p Span (f Span)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Span (f Span) -> p Inline (f Inline)
forall a. AsSpan a => Prism' a Span
Prism' Inline Span
_Span
data Quoted =
Quoted
QuoteType
[Inline]
deriving (Quoted -> Quoted -> Bool
(Quoted -> Quoted -> Bool)
-> (Quoted -> Quoted -> Bool) -> Eq Quoted
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Quoted -> Quoted -> Bool
== :: Quoted -> Quoted -> Bool
$c/= :: Quoted -> Quoted -> Bool
/= :: Quoted -> Quoted -> Bool
Eq, Eq Quoted
Eq Quoted =>
(Quoted -> Quoted -> Ordering)
-> (Quoted -> Quoted -> Bool)
-> (Quoted -> Quoted -> Bool)
-> (Quoted -> Quoted -> Bool)
-> (Quoted -> Quoted -> Bool)
-> (Quoted -> Quoted -> Quoted)
-> (Quoted -> Quoted -> Quoted)
-> Ord Quoted
Quoted -> Quoted -> Bool
Quoted -> Quoted -> Ordering
Quoted -> Quoted -> Quoted
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 :: Quoted -> Quoted -> Ordering
compare :: Quoted -> Quoted -> Ordering
$c< :: Quoted -> Quoted -> Bool
< :: Quoted -> Quoted -> Bool
$c<= :: Quoted -> Quoted -> Bool
<= :: Quoted -> Quoted -> Bool
$c> :: Quoted -> Quoted -> Bool
> :: Quoted -> Quoted -> Bool
$c>= :: Quoted -> Quoted -> Bool
>= :: Quoted -> Quoted -> Bool
$cmax :: Quoted -> Quoted -> Quoted
max :: Quoted -> Quoted -> Quoted
$cmin :: Quoted -> Quoted -> Quoted
min :: Quoted -> Quoted -> Quoted
Ord, Int -> Quoted -> ShowS
[Quoted] -> ShowS
Quoted -> String
(Int -> Quoted -> ShowS)
-> (Quoted -> String) -> ([Quoted] -> ShowS) -> Show Quoted
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Quoted -> ShowS
showsPrec :: Int -> Quoted -> ShowS
$cshow :: Quoted -> String
show :: Quoted -> String
$cshowList :: [Quoted] -> ShowS
showList :: [Quoted] -> ShowS
Show, Typeable Quoted
Typeable Quoted =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Quoted -> c Quoted)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Quoted)
-> (Quoted -> Constr)
-> (Quoted -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Quoted))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quoted))
-> ((forall b. Data b => b -> b) -> Quoted -> Quoted)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Quoted -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Quoted -> r)
-> (forall u. (forall d. Data d => d -> u) -> Quoted -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Quoted -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted)
-> Data Quoted
Quoted -> Constr
Quoted -> DataType
(forall b. Data b => b -> b) -> Quoted -> Quoted
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) -> Quoted -> u
forall u. (forall d. Data d => d -> u) -> Quoted -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Quoted
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Quoted -> c Quoted
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Quoted)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quoted)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Quoted -> c Quoted
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Quoted -> c Quoted
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Quoted
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Quoted
$ctoConstr :: Quoted -> Constr
toConstr :: Quoted -> Constr
$cdataTypeOf :: Quoted -> DataType
dataTypeOf :: Quoted -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Quoted)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Quoted)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quoted)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quoted)
$cgmapT :: (forall b. Data b => b -> b) -> Quoted -> Quoted
gmapT :: (forall b. Data b => b -> b) -> Quoted -> Quoted
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quoted -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Quoted -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Quoted -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Quoted -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Quoted -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Quoted -> m Quoted
Data, Typeable, ReadPrec [Quoted]
ReadPrec Quoted
Int -> ReadS Quoted
ReadS [Quoted]
(Int -> ReadS Quoted)
-> ReadS [Quoted]
-> ReadPrec Quoted
-> ReadPrec [Quoted]
-> Read Quoted
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Quoted
readsPrec :: Int -> ReadS Quoted
$creadList :: ReadS [Quoted]
readList :: ReadS [Quoted]
$creadPrec :: ReadPrec Quoted
readPrec :: ReadPrec Quoted
$creadListPrec :: ReadPrec [Quoted]
readListPrec :: ReadPrec [Quoted]
Read, (forall x. Quoted -> Rep Quoted x)
-> (forall x. Rep Quoted x -> Quoted) -> Generic Quoted
forall x. Rep Quoted x -> Quoted
forall x. Quoted -> Rep Quoted x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Quoted -> Rep Quoted x
from :: forall x. Quoted -> Rep Quoted x
$cto :: forall x. Rep Quoted x -> Quoted
to :: forall x. Rep Quoted x -> Quoted
Generic)
class HasQuoted a where
quoted ::
Lens' a Quoted
instance HasQuoted Quoted where
quoted :: Lens' Quoted Quoted
quoted =
(Quoted -> f Quoted) -> Quoted -> f Quoted
forall a. a -> a
id
instance HasInlines Quoted where
inlines :: Lens' Quoted [Inline]
inlines [Inline] -> f [Inline]
f (Quoted QuoteType
a [Inline]
i) =
([Inline] -> Quoted) -> f [Inline] -> f Quoted
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (QuoteType -> [Inline] -> Quoted
Quoted QuoteType
a) ([Inline] -> f [Inline]
f [Inline]
i)
instance HasQuoteType Quoted where
quoteType :: Lens' Quoted QuoteType
quoteType QuoteType -> f QuoteType
f (Quoted QuoteType
a [Inline]
i) =
(QuoteType -> Quoted) -> f QuoteType -> f Quoted
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (QuoteType -> [Inline] -> Quoted
`Quoted` [Inline]
i) (QuoteType -> f QuoteType
f QuoteType
a)
class AsQuoted a where
_Quoted ::
Prism' a Quoted
instance AsQuoted Quoted where
_Quoted :: Prism' Quoted Quoted
_Quoted =
p Quoted (f Quoted) -> p Quoted (f Quoted)
forall a. a -> a
id
instance AsQuoted Inline where
_Quoted :: Prism' Inline Quoted
_Quoted =
(Quoted -> Inline)
-> (Inline -> Maybe Quoted) -> Prism' Inline Quoted
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Quoted -> Inline
QuotedInline
(\case
QuotedInline Quoted
x -> Quoted -> Maybe Quoted
forall a. a -> Maybe a
Just Quoted
x
Inline
_ -> Maybe Quoted
forall a. Maybe a
Nothing)
instance AsQuoted D.Inline where
_Quoted :: Prism' Inline Quoted
_Quoted =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Quoted (f Quoted) -> p Inline (f Inline))
-> p Quoted (f Quoted)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Quoted (f Quoted) -> p Inline (f Inline)
forall a. AsQuoted a => Prism' a Quoted
Prism' Inline Quoted
_Quoted
data Cite =
Cite
[Citation]
[Inline]
deriving (Cite -> Cite -> Bool
(Cite -> Cite -> Bool) -> (Cite -> Cite -> Bool) -> Eq Cite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cite -> Cite -> Bool
== :: Cite -> Cite -> Bool
$c/= :: Cite -> Cite -> Bool
/= :: Cite -> Cite -> Bool
Eq, Eq Cite
Eq Cite =>
(Cite -> Cite -> Ordering)
-> (Cite -> Cite -> Bool)
-> (Cite -> Cite -> Bool)
-> (Cite -> Cite -> Bool)
-> (Cite -> Cite -> Bool)
-> (Cite -> Cite -> Cite)
-> (Cite -> Cite -> Cite)
-> Ord Cite
Cite -> Cite -> Bool
Cite -> Cite -> Ordering
Cite -> Cite -> Cite
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 :: Cite -> Cite -> Ordering
compare :: Cite -> Cite -> Ordering
$c< :: Cite -> Cite -> Bool
< :: Cite -> Cite -> Bool
$c<= :: Cite -> Cite -> Bool
<= :: Cite -> Cite -> Bool
$c> :: Cite -> Cite -> Bool
> :: Cite -> Cite -> Bool
$c>= :: Cite -> Cite -> Bool
>= :: Cite -> Cite -> Bool
$cmax :: Cite -> Cite -> Cite
max :: Cite -> Cite -> Cite
$cmin :: Cite -> Cite -> Cite
min :: Cite -> Cite -> Cite
Ord, Int -> Cite -> ShowS
[Cite] -> ShowS
Cite -> String
(Int -> Cite -> ShowS)
-> (Cite -> String) -> ([Cite] -> ShowS) -> Show Cite
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cite -> ShowS
showsPrec :: Int -> Cite -> ShowS
$cshow :: Cite -> String
show :: Cite -> String
$cshowList :: [Cite] -> ShowS
showList :: [Cite] -> ShowS
Show, Typeable Cite
Typeable Cite =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cite -> c Cite)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cite)
-> (Cite -> Constr)
-> (Cite -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cite))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite))
-> ((forall b. Data b => b -> b) -> Cite -> Cite)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r)
-> (forall u. (forall d. Data d => d -> u) -> Cite -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Cite -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite)
-> Data Cite
Cite -> Constr
Cite -> DataType
(forall b. Data b => b -> b) -> Cite -> Cite
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) -> Cite -> u
forall u. (forall d. Data d => d -> u) -> Cite -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cite
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cite -> c Cite
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cite)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cite -> c Cite
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cite -> c Cite
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cite
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cite
$ctoConstr :: Cite -> Constr
toConstr :: Cite -> Constr
$cdataTypeOf :: Cite -> DataType
dataTypeOf :: Cite -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cite)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cite)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite)
$cgmapT :: (forall b. Data b => b -> b) -> Cite -> Cite
gmapT :: (forall b. Data b => b -> b) -> Cite -> Cite
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Cite -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Cite -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cite -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cite -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cite -> m Cite
Data, Typeable, ReadPrec [Cite]
ReadPrec Cite
Int -> ReadS Cite
ReadS [Cite]
(Int -> ReadS Cite)
-> ReadS [Cite] -> ReadPrec Cite -> ReadPrec [Cite] -> Read Cite
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Cite
readsPrec :: Int -> ReadS Cite
$creadList :: ReadS [Cite]
readList :: ReadS [Cite]
$creadPrec :: ReadPrec Cite
readPrec :: ReadPrec Cite
$creadListPrec :: ReadPrec [Cite]
readListPrec :: ReadPrec [Cite]
Read, (forall x. Cite -> Rep Cite x)
-> (forall x. Rep Cite x -> Cite) -> Generic Cite
forall x. Rep Cite x -> Cite
forall x. Cite -> Rep Cite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Cite -> Rep Cite x
from :: forall x. Cite -> Rep Cite x
$cto :: forall x. Rep Cite x -> Cite
to :: forall x. Rep Cite x -> Cite
Generic)
instance Semigroup Cite where
Cite [Citation]
c1 [Inline]
i1 <> :: Cite -> Cite -> Cite
<> Cite [Citation]
c2 [Inline]
i2 =
[Citation] -> [Inline] -> Cite
Cite ([Citation]
c1 [Citation] -> [Citation] -> [Citation]
forall a. Semigroup a => a -> a -> a
<> [Citation]
c2) ([Inline]
i1 [Inline] -> [Inline] -> [Inline]
forall a. Semigroup a => a -> a -> a
<> [Inline]
i2)
instance Monoid Cite where
mempty :: Cite
mempty =
[Citation] -> [Inline] -> Cite
Cite [Citation]
forall a. Monoid a => a
mempty [Inline]
forall a. Monoid a => a
mempty
class HasCite a where
cite ::
Lens' a Cite
citeCitations ::
Lens' a [Citation]
citeCitations =
(Cite -> f Cite) -> a -> f a
forall a. HasCite a => Lens' a Cite
Lens' a Cite
cite ((Cite -> f Cite) -> a -> f a)
-> (([Citation] -> f [Citation]) -> Cite -> f Cite)
-> ([Citation] -> f [Citation])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Citation] -> f [Citation]) -> Cite -> f Cite
forall a. HasCite a => Lens' a [Citation]
Lens' Cite [Citation]
citeCitations
instance HasCite Cite where
cite :: Lens' Cite Cite
cite =
(Cite -> f Cite) -> Cite -> f Cite
forall a. a -> a
id
citeCitations :: Lens' Cite [Citation]
citeCitations [Citation] -> f [Citation]
f (Cite [Citation]
a [Inline]
i) =
([Citation] -> Cite) -> f [Citation] -> f Cite
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Citation] -> [Inline] -> Cite
`Cite` [Inline]
i) ([Citation] -> f [Citation]
f [Citation]
a)
instance HasInlines Cite where
inlines :: Lens' Cite [Inline]
inlines [Inline] -> f [Inline]
f (Cite [Citation]
a [Inline]
i) =
([Inline] -> Cite) -> f [Inline] -> f Cite
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Citation] -> [Inline] -> Cite
Cite [Citation]
a) ([Inline] -> f [Inline]
f [Inline]
i)
class AsCite a where
_Cite ::
Prism' a Cite
instance AsCite Cite where
_Cite :: Prism' Cite Cite
_Cite =
p Cite (f Cite) -> p Cite (f Cite)
forall a. a -> a
id
instance AsCite Inline where
_Cite :: Prism' Inline Cite
_Cite =
(Cite -> Inline) -> (Inline -> Maybe Cite) -> Prism' Inline Cite
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Cite -> Inline
CiteInline
(\case
CiteInline Cite
x -> Cite -> Maybe Cite
forall a. a -> Maybe a
Just Cite
x
Inline
_ -> Maybe Cite
forall a. Maybe a
Nothing)
instance AsCite D.Inline where
_Cite :: Prism' Inline Cite
_Cite =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Cite (f Cite) -> p Inline (f Inline))
-> p Cite (f Cite)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Cite (f Cite) -> p Inline (f Inline)
forall a. AsCite a => Prism' a Cite
Prism' Inline Cite
_Cite
data Math =
Math
MathType
Text
deriving (Math -> Math -> Bool
(Math -> Math -> Bool) -> (Math -> Math -> Bool) -> Eq Math
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Math -> Math -> Bool
== :: Math -> Math -> Bool
$c/= :: Math -> Math -> Bool
/= :: Math -> Math -> Bool
Eq, Eq Math
Eq Math =>
(Math -> Math -> Ordering)
-> (Math -> Math -> Bool)
-> (Math -> Math -> Bool)
-> (Math -> Math -> Bool)
-> (Math -> Math -> Bool)
-> (Math -> Math -> Math)
-> (Math -> Math -> Math)
-> Ord Math
Math -> Math -> Bool
Math -> Math -> Ordering
Math -> Math -> Math
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 :: Math -> Math -> Ordering
compare :: Math -> Math -> Ordering
$c< :: Math -> Math -> Bool
< :: Math -> Math -> Bool
$c<= :: Math -> Math -> Bool
<= :: Math -> Math -> Bool
$c> :: Math -> Math -> Bool
> :: Math -> Math -> Bool
$c>= :: Math -> Math -> Bool
>= :: Math -> Math -> Bool
$cmax :: Math -> Math -> Math
max :: Math -> Math -> Math
$cmin :: Math -> Math -> Math
min :: Math -> Math -> Math
Ord, Int -> Math -> ShowS
[Math] -> ShowS
Math -> String
(Int -> Math -> ShowS)
-> (Math -> String) -> ([Math] -> ShowS) -> Show Math
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Math -> ShowS
showsPrec :: Int -> Math -> ShowS
$cshow :: Math -> String
show :: Math -> String
$cshowList :: [Math] -> ShowS
showList :: [Math] -> ShowS
Show, Typeable Math
Typeable Math =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Math -> c Math)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Math)
-> (Math -> Constr)
-> (Math -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Math))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Math))
-> ((forall b. Data b => b -> b) -> Math -> Math)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r)
-> (forall u. (forall d. Data d => d -> u) -> Math -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Math -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Math -> m Math)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math)
-> Data Math
Math -> Constr
Math -> DataType
(forall b. Data b => b -> b) -> Math -> Math
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) -> Math -> u
forall u. (forall d. Data d => d -> u) -> Math -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Math -> m Math
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Math
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Math -> c Math
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Math)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Math)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Math -> c Math
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Math -> c Math
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Math
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Math
$ctoConstr :: Math -> Constr
toConstr :: Math -> Constr
$cdataTypeOf :: Math -> DataType
dataTypeOf :: Math -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Math)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Math)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Math)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Math)
$cgmapT :: (forall b. Data b => b -> b) -> Math -> Math
gmapT :: (forall b. Data b => b -> b) -> Math -> Math
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Math -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Math -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Math -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Math -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Math -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Math -> m Math
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Math -> m Math
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Math -> m Math
Data, Typeable, ReadPrec [Math]
ReadPrec Math
Int -> ReadS Math
ReadS [Math]
(Int -> ReadS Math)
-> ReadS [Math] -> ReadPrec Math -> ReadPrec [Math] -> Read Math
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Math
readsPrec :: Int -> ReadS Math
$creadList :: ReadS [Math]
readList :: ReadS [Math]
$creadPrec :: ReadPrec Math
readPrec :: ReadPrec Math
$creadListPrec :: ReadPrec [Math]
readListPrec :: ReadPrec [Math]
Read, (forall x. Math -> Rep Math x)
-> (forall x. Rep Math x -> Math) -> Generic Math
forall x. Rep Math x -> Math
forall x. Math -> Rep Math x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Math -> Rep Math x
from :: forall x. Math -> Rep Math x
$cto :: forall x. Rep Math x -> Math
to :: forall x. Rep Math x -> Math
Generic)
class HasMath a where
math ::
Lens' a Math
instance HasMath Math where
math :: Lens' Math Math
math =
(Math -> f Math) -> Math -> f Math
forall a. a -> a
id
instance HasMathType Math where
mathType :: Lens' Math MathType
mathType MathType -> f MathType
f (Math MathType
a Text
i) =
(MathType -> Math) -> f MathType -> f Math
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (MathType -> Text -> Math
`Math` Text
i) (MathType -> f MathType
f MathType
a)
instance HasText Math where
text :: Lens' Math Text
text Text -> f Text
f (Math MathType
a Text
i) =
(Text -> Math) -> f Text -> f Math
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (MathType -> Text -> Math
Math MathType
a) (Text -> f Text
f Text
i)
class AsMath a where
_Math ::
Prism' a Math
instance AsMath Math where
_Math :: Prism' Math Math
_Math =
p Math (f Math) -> p Math (f Math)
forall a. a -> a
id
instance AsMath Inline where
_Math :: Prism' Inline Math
_Math =
(Math -> Inline) -> (Inline -> Maybe Math) -> Prism' Inline Math
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Math -> Inline
MathInline
(\case
MathInline Math
x -> Math -> Maybe Math
forall a. a -> Maybe a
Just Math
x
Inline
_ -> Maybe Math
forall a. Maybe a
Nothing)
instance AsMath D.Inline where
_Math :: Prism' Inline Math
_Math =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Math (f Math) -> p Inline (f Inline))
-> p Math (f Math)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Math (f Math) -> p Inline (f Inline)
forall a. AsMath a => Prism' a Math
Prism' Inline Math
_Math
data Inline =
Str Text
| Emph [Inline]
| Underline [Inline]
| Strong [Inline]
| Strikeout [Inline]
| Superscript [Inline]
| Subscript [Inline]
| SmallCaps [Inline]
| QuotedInline Quoted
| CiteInline Cite
| CodeInline Code
| Space
| SoftBreak
| LineBreak
| MathInline Math
| RawInline Raw
| LinkInline Link
| ImageInline Image
| Note [Block]
| SpanInline Span
deriving (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, 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, 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, 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, Typeable, ReadPrec [Inline]
ReadPrec Inline
Int -> ReadS Inline
ReadS [Inline]
(Int -> ReadS Inline)
-> ReadS [Inline]
-> ReadPrec Inline
-> ReadPrec [Inline]
-> Read Inline
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Inline
readsPrec :: Int -> ReadS Inline
$creadList :: ReadS [Inline]
readList :: ReadS [Inline]
$creadPrec :: ReadPrec Inline
readPrec :: ReadPrec Inline
$creadListPrec :: ReadPrec [Inline]
readListPrec :: ReadPrec [Inline]
Read, (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)
class HasInline a where
inline ::
Lens' a Inline
instance HasInline Inline where
inline :: Lens' Inline Inline
inline =
(Inline -> f Inline) -> Inline -> f Inline
forall a. a -> a
id
instance HasInline D.Inline where
inline :: Lens' Inline Inline
inline =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline
class AsInline a where
_Inline ::
Prism' a Inline
_Str ::
Prism' a Text
_Str =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p Text (f Text) -> p Inline (f Inline))
-> p Text (f Text)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Text (f Text) -> p Inline (f Inline)
forall a. AsInline a => Prism' a Text
Prism' Inline Text
_Str
_Emph ::
Prism' a [Inline]
_Emph =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_Emph
_Underline ::
Prism' a [Inline]
_Underline =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_Underline
_Strong ::
Prism' a [Inline]
_Strong =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_Strong
_Strikeout ::
Prism' a [Inline]
_Strikeout =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_Strikeout
_Superscript ::
Prism' a [Inline]
_Superscript =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_Superscript
_Subscript ::
Prism' a [Inline]
_Subscript =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_Subscript
_SmallCaps ::
Prism' a [Inline]
_SmallCaps =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Inline] (f [Inline]) -> p Inline (f Inline))
-> p [Inline] (f [Inline])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Inline] (f [Inline]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Inline]
Prism' Inline [Inline]
_SmallCaps
_Space ::
Prism' a ()
_Space =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p () (f ()) -> p Inline (f Inline)) -> p () (f ()) -> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Inline (f Inline)
forall a. AsInline a => Prism' a ()
Prism' Inline ()
_Space
_SoftBreak ::
Prism' a ()
_SoftBreak =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p () (f ()) -> p Inline (f Inline)) -> p () (f ()) -> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Inline (f Inline)
forall a. AsInline a => Prism' a ()
Prism' Inline ()
_SoftBreak
_LineBreak ::
Prism' a ()
_LineBreak =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p () (f ()) -> p Inline (f Inline)) -> p () (f ()) -> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p () (f ()) -> p Inline (f Inline)
forall a. AsInline a => Prism' a ()
Prism' Inline ()
_LineBreak
_Note ::
Prism' a [Block]
_Note =
p Inline (f Inline) -> p a (f a)
forall a. AsInline a => Prism' a Inline
Prism' a Inline
_Inline (p Inline (f Inline) -> p a (f a))
-> (p [Block] (f [Block]) -> p Inline (f Inline))
-> p [Block] (f [Block])
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p [Block] (f [Block]) -> p Inline (f Inline)
forall a. AsInline a => Prism' a [Block]
Prism' Inline [Block]
_Note
instance AsInline Inline where
_Inline :: Prism' Inline Inline
_Inline =
p Inline (f Inline) -> p Inline (f Inline)
forall a. a -> a
id
_Str :: Prism' Inline Text
_Str =
(Text -> Inline) -> (Inline -> Maybe Text) -> Prism' Inline Text
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Text -> Inline
Str
(\case
Str Text
x -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
x
Inline
_ -> Maybe Text
forall a. Maybe a
Nothing)
_Emph :: Prism' Inline [Inline]
_Emph =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
Emph
(\case
Emph [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Underline :: Prism' Inline [Inline]
_Underline =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
Underline
(\case
Underline [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Strong :: Prism' Inline [Inline]
_Strong =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
Strong
(\case
Strong [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Strikeout :: Prism' Inline [Inline]
_Strikeout =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
Strikeout
(\case
Strikeout [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Superscript :: Prism' Inline [Inline]
_Superscript =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
Superscript
(\case
Superscript [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Subscript :: Prism' Inline [Inline]
_Subscript =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
Subscript
(\case
Subscript [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_SmallCaps :: Prism' Inline [Inline]
_SmallCaps =
([Inline] -> Inline)
-> (Inline -> Maybe [Inline]) -> Prism' Inline [Inline]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Inline] -> Inline
SmallCaps
(\case
SmallCaps [Inline]
x -> [Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just [Inline]
x
Inline
_ -> Maybe [Inline]
forall a. Maybe a
Nothing)
_Space :: Prism' Inline ()
_Space =
(() -> Inline) -> (Inline -> Maybe ()) -> Prism' Inline ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Inline
Space)
(\case
Inline
Space -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Inline
_ -> Maybe ()
forall a. Maybe a
Nothing)
_SoftBreak :: Prism' Inline ()
_SoftBreak =
(() -> Inline) -> (Inline -> Maybe ()) -> Prism' Inline ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Inline
SoftBreak)
(\case
Inline
SoftBreak -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Inline
_ -> Maybe ()
forall a. Maybe a
Nothing)
_LineBreak :: Prism' Inline ()
_LineBreak =
(() -> Inline) -> (Inline -> Maybe ()) -> Prism' Inline ()
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
(\() -> Inline
LineBreak)
(\case
Inline
LineBreak -> () -> Maybe ()
forall a. a -> Maybe a
Just ()
Inline
_ -> Maybe ()
forall a. Maybe a
Nothing)
_Note :: Prism' Inline [Block]
_Note =
([Block] -> Inline)
-> (Inline -> Maybe [Block]) -> Prism' Inline [Block]
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
[Block] -> Inline
Note
(\case
Note [Block]
x -> [Block] -> Maybe [Block]
forall a. a -> Maybe a
Just [Block]
x
Inline
_ -> Maybe [Block]
forall a. Maybe a
Nothing)
instance AsInline D.Inline where
_Inline :: Prism' Inline Inline
_Inline =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline
instance AsCode Inline where
_Code :: Prism' Inline Code
_Code =
(Code -> Inline) -> (Inline -> Maybe Code) -> Prism' Inline Code
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Code -> Inline
CodeInline
(\case
CodeInline Code
x -> Code -> Maybe Code
forall a. a -> Maybe a
Just Code
x
Inline
_ -> Maybe Code
forall a. Maybe a
Nothing)
instance AsCode D.Inline where
_Code :: Prism' Inline Code
_Code =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Code (f Code) -> p Inline (f Inline))
-> p Code (f Code)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Code (f Code) -> p Inline (f Inline)
forall a. AsCode a => Prism' a Code
Prism' Inline Code
_Code
instance AsRaw Inline where
_Raw :: Prism' Inline Raw
_Raw =
(Raw -> Inline) -> (Inline -> Maybe Raw) -> Prism' Inline Raw
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism'
Raw -> Inline
RawInline
(\case
RawInline Raw
x -> Raw -> Maybe Raw
forall a. a -> Maybe a
Just Raw
x
Inline
_ -> Maybe Raw
forall a. Maybe a
Nothing)
instance AsRaw D.Inline where
_Raw :: Prism' Inline Raw
_Raw =
AnIso Inline Inline Inline Inline
-> Iso Inline Inline Inline Inline
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Inline Inline Inline Inline
Iso' Inline Inline
isInline (p Inline (f Inline) -> p Inline (f Inline))
-> (p Raw (f Raw) -> p Inline (f Inline))
-> p Raw (f Raw)
-> p Inline (f Inline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Raw (f Raw) -> p Inline (f Inline)
forall a. AsRaw a => Prism' a Raw
Prism' Inline Raw
_Raw
instance Plated Inline where
plate :: Traversal' Inline Inline
plate Inline -> f Inline
_ (Str Text
t) =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Inline
Str Text
t)
plate Inline -> f Inline
f (Emph [Inline]
i) =
[Inline] -> Inline
Emph ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (Underline [Inline]
i) =
[Inline] -> Inline
Underline ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (Strong [Inline]
i) =
[Inline] -> Inline
Strong ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (Strikeout [Inline]
i) =
[Inline] -> Inline
Strikeout ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (Superscript [Inline]
i) =
[Inline] -> Inline
Superscript ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (Subscript [Inline]
i) =
[Inline] -> Inline
Subscript ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (SmallCaps [Inline]
i) =
[Inline] -> Inline
SmallCaps ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (QuotedInline (Quoted QuoteType
q [Inline]
i)) =
Quoted -> Inline
QuotedInline (Quoted -> Inline) -> ([Inline] -> Quoted) -> [Inline] -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuoteType -> [Inline] -> Quoted
Quoted QuoteType
q ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (CiteInline (Cite [Citation]
c [Inline]
i)) =
Cite -> Inline
CiteInline (Cite -> Inline) -> ([Inline] -> Cite) -> [Inline] -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Citation] -> [Inline] -> Cite
Cite [Citation]
c ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
_ (CodeInline Code
x) =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Code -> Inline
CodeInline Code
x)
plate Inline -> f Inline
_ Inline
Space =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inline
Space
plate Inline -> f Inline
_ Inline
SoftBreak =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inline
SoftBreak
plate Inline -> f Inline
_ Inline
LineBreak =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inline
LineBreak
plate Inline -> f Inline
_ (MathInline Math
x) =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Math -> Inline
MathInline Math
x)
plate Inline -> f Inline
_ (RawInline Raw
x) =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Raw -> Inline
RawInline Raw
x)
plate Inline -> f Inline
f (LinkInline (Link Attr
a [Inline]
i Target
t)) =
(\[Inline]
i' -> Link -> Inline
LinkInline (Attr -> [Inline] -> Target -> Link
Link Attr
a [Inline]
i' Target
t)) ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
f (ImageInline (Image Attr
a [Inline]
i Target
t)) =
(\[Inline]
i' -> Image -> Inline
ImageInline (Attr -> [Inline] -> Target -> Image
Image Attr
a [Inline]
i' Target
t)) ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
plate Inline -> f Inline
_ (Note [Block]
b) =
Inline -> f Inline
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Block] -> Inline
Note [Block]
b)
plate Inline -> f Inline
f (SpanInline (Span Attr
a [Inline]
i)) =
Span -> Inline
SpanInline (Span -> Inline) -> ([Inline] -> Span) -> [Inline] -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> [Inline] -> Span
Span Attr
a ([Inline] -> Inline) -> f [Inline] -> f Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> f Inline) -> [Inline] -> f [Inline]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Inline -> f Inline
f [Inline]
i
isInline ::
Iso'
Inline
D.Inline
isInline :: Iso' Inline Inline
isInline =
(Inline -> Inline) -> (Inline -> Inline) -> Iso' Inline Inline
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\case
Str Text
t -> Text -> Inline
D.Str Text
t
Emph [Inline]
i -> ShortCaption -> Inline
D.Emph ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
Underline [Inline]
i -> ShortCaption -> Inline
D.Underline ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
Strong [Inline]
i -> ShortCaption -> Inline
D.Strong ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
Strikeout [Inline]
i -> ShortCaption -> Inline
D.Strikeout ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
Superscript [Inline]
i -> ShortCaption -> Inline
D.Superscript ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
Subscript [Inline]
i -> ShortCaption -> Inline
D.Subscript ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
SmallCaps [Inline]
i -> ShortCaption -> Inline
D.SmallCaps ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
QuotedInline (Quoted QuoteType
t [Inline]
i) -> QuoteType -> ShortCaption -> Inline
D.Quoted (Getting QuoteType QuoteType QuoteType -> QuoteType -> QuoteType
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting QuoteType QuoteType QuoteType
Iso' QuoteType QuoteType
isQuoteType QuoteType
t) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
CiteInline (Cite [Citation]
c [Inline]
i) -> [Citation] -> ShortCaption -> Inline
D.Cite ((Citation -> Citation) -> [Citation] -> [Citation]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Citation Citation Citation -> Citation -> Citation
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Citation Citation Citation
Iso' Citation Citation
isCitation) [Citation]
c) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
CodeInline (Code Attr
a Text
t) -> Attr -> Text -> Inline
D.Code (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) Text
t
Inline
Space -> Inline
D.Space
Inline
SoftBreak -> Inline
D.SoftBreak
Inline
LineBreak -> Inline
D.LineBreak
MathInline (Math MathType
m Text
t) -> MathType -> Text -> Inline
D.Math (Getting MathType MathType MathType -> MathType -> MathType
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting MathType MathType MathType
Iso' MathType MathType
isMathType MathType
m) Text
t
RawInline (Raw Format
f Text
t) -> Format -> Text -> Inline
D.RawInline (Getting Format Format Format -> Format -> Format
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Format Format Format
Iso Format Format Format Format
isFormat Format
f) Text
t
LinkInline (Link Attr
a [Inline]
i Target
t) -> Attr -> ShortCaption -> (Text, Text) -> Inline
D.Link (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i) (Getting (Text, Text) Target (Text, Text) -> Target -> (Text, Text)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Text, Text) Target (Text, Text)
Iso' Target (Text, Text)
isTarget Target
t)
ImageInline (Image Attr
a [Inline]
i Target
t) -> Attr -> ShortCaption -> (Text, Text) -> Inline
D.Image (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i) (Getting (Text, Text) Target (Text, Text) -> Target -> (Text, Text)
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Text, Text) Target (Text, Text)
Iso' Target (Text, Text)
isTarget Target
t)
Note [Block]
b -> [Block] -> Inline
D.Note ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Block Block Block -> Block -> Block
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Block Block Block
Iso' Block Block
isBlock) [Block]
b)
SpanInline (Span Attr
a [Inline]
i) -> Attr -> ShortCaption -> Inline
D.Span (Getting Attr Attr Attr -> Attr -> Attr
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Attr Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
i)
)
(\case
D.Str Text
t -> Text -> Inline
Str Text
t
D.Emph ShortCaption
i -> [Inline] -> Inline
Emph ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Underline ShortCaption
i -> [Inline] -> Inline
Underline ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Strong ShortCaption
i -> [Inline] -> Inline
Strong ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Strikeout ShortCaption
i -> [Inline] -> Inline
Strikeout ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Superscript ShortCaption
i -> [Inline] -> Inline
Superscript ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Subscript ShortCaption
i -> [Inline] -> Inline
Subscript ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.SmallCaps ShortCaption
i -> [Inline] -> Inline
SmallCaps ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i)
D.Quoted QuoteType
t ShortCaption
i -> Quoted -> Inline
QuotedInline (QuoteType -> [Inline] -> Quoted
Quoted (AReview QuoteType QuoteType -> QuoteType -> QuoteType
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview QuoteType QuoteType
Iso' QuoteType QuoteType
isQuoteType QuoteType
t) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i))
D.Cite [Citation]
c ShortCaption
i -> Cite -> Inline
CiteInline ([Citation] -> [Inline] -> Cite
Cite ((Citation -> Citation) -> [Citation] -> [Citation]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Citation Citation -> Citation -> Citation
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Citation Citation
Iso' Citation Citation
isCitation) [Citation]
c) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i))
D.Code Attr
a Text
t -> Code -> Inline
CodeInline (Attr -> Text -> Code
Code (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) Text
t)
Inline
D.Space -> Inline
Space
Inline
D.SoftBreak -> Inline
SoftBreak
Inline
D.LineBreak -> Inline
LineBreak
D.Math MathType
m Text
t -> Math -> Inline
MathInline (MathType -> Text -> Math
Math (AReview MathType MathType -> MathType -> MathType
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview MathType MathType
Iso' MathType MathType
isMathType MathType
m) Text
t)
D.RawInline Format
f Text
t -> Raw -> Inline
RawInline (Format -> Text -> Raw
Raw (AReview Format Format -> Format -> Format
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Format Format
Iso Format Format Format Format
isFormat Format
f) Text
t)
D.Link Attr
a ShortCaption
i (Text, Text)
t -> Link -> Inline
LinkInline (Attr -> [Inline] -> Target -> Link
Link (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i) (AReview Target (Text, Text) -> (Text, Text) -> Target
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Target (Text, Text)
Iso' Target (Text, Text)
isTarget (Text, Text)
t))
D.Image Attr
a ShortCaption
i (Text, Text)
t -> Image -> Inline
ImageInline (Attr -> [Inline] -> Target -> Image
Image (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i) (AReview Target (Text, Text) -> (Text, Text) -> Target
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Target (Text, Text)
Iso' Target (Text, Text)
isTarget (Text, Text)
t))
D.Note [Block]
b -> [Block] -> Inline
Note ((Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Block Block -> Block -> Block
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Block Block
Iso' Block Block
isBlock) [Block]
b)
D.Span Attr
a ShortCaption
i -> Span -> Inline
SpanInline (Attr -> [Inline] -> Span
Span (AReview Attr Attr -> Attr -> Attr
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Attr Attr
Iso' Attr Attr
isAttr Attr
a) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
i))
)
instance Walkable D.Inline Inline where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Inline -> m Inline) -> Inline -> m Inline
walkM =
(Inline -> m Inline) -> Inline -> m Inline
Iso' Inline Inline
isInline
query :: forall c. Monoid c => (Inline -> c) -> Inline -> c
query Inline -> c
f =
Inline -> c
f (Inline -> c) -> (Inline -> Inline) -> Inline -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline
data Citation =
Citation
Text
[Inline]
[Inline]
CitationMode
Int
Int
deriving (Citation -> Citation -> Bool
(Citation -> Citation -> Bool)
-> (Citation -> Citation -> Bool) -> Eq Citation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Citation -> Citation -> Bool
== :: Citation -> Citation -> Bool
$c/= :: Citation -> Citation -> Bool
/= :: Citation -> Citation -> Bool
Eq, Eq Citation
Eq Citation =>
(Citation -> Citation -> Ordering)
-> (Citation -> Citation -> Bool)
-> (Citation -> Citation -> Bool)
-> (Citation -> Citation -> Bool)
-> (Citation -> Citation -> Bool)
-> (Citation -> Citation -> Citation)
-> (Citation -> Citation -> Citation)
-> Ord Citation
Citation -> Citation -> Bool
Citation -> Citation -> Ordering
Citation -> Citation -> Citation
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 :: Citation -> Citation -> Ordering
compare :: Citation -> Citation -> Ordering
$c< :: Citation -> Citation -> Bool
< :: Citation -> Citation -> Bool
$c<= :: Citation -> Citation -> Bool
<= :: Citation -> Citation -> Bool
$c> :: Citation -> Citation -> Bool
> :: Citation -> Citation -> Bool
$c>= :: Citation -> Citation -> Bool
>= :: Citation -> Citation -> Bool
$cmax :: Citation -> Citation -> Citation
max :: Citation -> Citation -> Citation
$cmin :: Citation -> Citation -> Citation
min :: Citation -> Citation -> Citation
Ord, Int -> Citation -> ShowS
[Citation] -> ShowS
Citation -> String
(Int -> Citation -> ShowS)
-> (Citation -> String) -> ([Citation] -> ShowS) -> Show Citation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Citation -> ShowS
showsPrec :: Int -> Citation -> ShowS
$cshow :: Citation -> String
show :: Citation -> String
$cshowList :: [Citation] -> ShowS
showList :: [Citation] -> ShowS
Show, Typeable Citation
Typeable Citation =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Citation -> c Citation)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Citation)
-> (Citation -> Constr)
-> (Citation -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Citation))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation))
-> ((forall b. Data b => b -> b) -> Citation -> Citation)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r)
-> (forall u. (forall d. Data d => d -> u) -> Citation -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Citation -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation)
-> Data Citation
Citation -> Constr
Citation -> DataType
(forall b. Data b => b -> b) -> Citation -> Citation
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) -> Citation -> u
forall u. (forall d. Data d => d -> u) -> Citation -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Citation
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Citation -> c Citation
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Citation)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Citation -> c Citation
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Citation -> c Citation
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Citation
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Citation
$ctoConstr :: Citation -> Constr
toConstr :: Citation -> Constr
$cdataTypeOf :: Citation -> DataType
dataTypeOf :: Citation -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Citation)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Citation)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation)
$cgmapT :: (forall b. Data b => b -> b) -> Citation -> Citation
gmapT :: (forall b. Data b => b -> b) -> Citation -> Citation
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Citation -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Citation -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Citation -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Citation -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Citation -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Citation -> m Citation
Data, Typeable, ReadPrec [Citation]
ReadPrec Citation
Int -> ReadS Citation
ReadS [Citation]
(Int -> ReadS Citation)
-> ReadS [Citation]
-> ReadPrec Citation
-> ReadPrec [Citation]
-> Read Citation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Citation
readsPrec :: Int -> ReadS Citation
$creadList :: ReadS [Citation]
readList :: ReadS [Citation]
$creadPrec :: ReadPrec Citation
readPrec :: ReadPrec Citation
$creadListPrec :: ReadPrec [Citation]
readListPrec :: ReadPrec [Citation]
Read, (forall x. Citation -> Rep Citation x)
-> (forall x. Rep Citation x -> Citation) -> Generic Citation
forall x. Rep Citation x -> Citation
forall x. Citation -> Rep Citation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Citation -> Rep Citation x
from :: forall x. Citation -> Rep Citation x
$cto :: forall x. Rep Citation x -> Citation
to :: forall x. Rep Citation x -> Citation
Generic)
class HasCitation a where
citation ::
Lens' a Citation
citationId ::
Lens' a Text
citationId =
(Citation -> f Citation) -> a -> f a
forall a. HasCitation a => Lens' a Citation
Lens' a Citation
citation ((Citation -> f Citation) -> a -> f a)
-> ((Text -> f Text) -> Citation -> f Citation)
-> (Text -> f Text)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> f Text) -> Citation -> f Citation
forall a. HasCitation a => Lens' a Text
Lens' Citation Text
citationId
citationPrefix ::
Lens' a [Inline]
citationPrefix =
(Citation -> f Citation) -> a -> f a
forall a. HasCitation a => Lens' a Citation
Lens' a Citation
citation ((Citation -> f Citation) -> a -> f a)
-> (([Inline] -> f [Inline]) -> Citation -> f Citation)
-> ([Inline] -> f [Inline])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Inline] -> f [Inline]) -> Citation -> f Citation
forall a. HasCitation a => Lens' a [Inline]
Lens' Citation [Inline]
citationPrefix
citationSuffix ::
Lens' a [Inline]
citationSuffix =
(Citation -> f Citation) -> a -> f a
forall a. HasCitation a => Lens' a Citation
Lens' a Citation
citation ((Citation -> f Citation) -> a -> f a)
-> (([Inline] -> f [Inline]) -> Citation -> f Citation)
-> ([Inline] -> f [Inline])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Inline] -> f [Inline]) -> Citation -> f Citation
forall a. HasCitation a => Lens' a [Inline]
Lens' Citation [Inline]
citationSuffix
citationNoteNum ::
Lens' a Int
citationNoteNum =
(Citation -> f Citation) -> a -> f a
forall a. HasCitation a => Lens' a Citation
Lens' a Citation
citation ((Citation -> f Citation) -> a -> f a)
-> ((Int -> f Int) -> Citation -> f Citation)
-> (Int -> f Int)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> f Int) -> Citation -> f Citation
forall a. HasCitation a => Lens' a Int
Lens' Citation Int
citationNoteNum
citationHash ::
Lens' a Int
citationHash =
(Citation -> f Citation) -> a -> f a
forall a. HasCitation a => Lens' a Citation
Lens' a Citation
citation ((Citation -> f Citation) -> a -> f a)
-> ((Int -> f Int) -> Citation -> f Citation)
-> (Int -> f Int)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> f Int) -> Citation -> f Citation
forall a. HasCitation a => Lens' a Int
Lens' Citation Int
citationHash
instance HasCitation Citation where
citation :: Lens' Citation Citation
citation =
(Citation -> f Citation) -> Citation -> f Citation
forall a. a -> a
id
citationId :: Lens' Citation Text
citationId Text -> f Text
f (Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) =
(Text -> Citation) -> f Text -> f Citation
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Text
i' -> Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i' [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) (Text -> f Text
f Text
i)
citationPrefix :: Lens' Citation [Inline]
citationPrefix [Inline] -> f [Inline]
f (Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) =
([Inline] -> Citation) -> f [Inline] -> f Citation
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Inline]
p' -> Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i [Inline]
p' [Inline]
s CitationMode
m Int
n Int
h) ([Inline] -> f [Inline]
f [Inline]
p)
citationSuffix :: Lens' Citation [Inline]
citationSuffix [Inline] -> f [Inline]
f (Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) =
([Inline] -> Citation) -> f [Inline] -> f Citation
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[Inline]
s' -> Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i [Inline]
p [Inline]
s' CitationMode
m Int
n Int
h) ([Inline] -> f [Inline]
f [Inline]
s)
citationNoteNum :: Lens' Citation Int
citationNoteNum Int -> f Int
f (Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) =
(Int -> Citation) -> f Int -> f Citation
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Int
n' -> Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n' Int
h) (Int -> f Int
f Int
n)
citationHash :: Lens' Citation Int
citationHash Int -> f Int
f (Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) =
(Int -> Citation) -> f Int -> f Citation
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n) (Int -> f Int
f Int
h)
instance HasCitationMode Citation where
citationMode :: Lens' Citation CitationMode
citationMode CitationMode -> f CitationMode
f (Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) =
(CitationMode -> Citation) -> f CitationMode -> f Citation
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\CitationMode
m' -> Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i [Inline]
p [Inline]
s CitationMode
m' Int
n Int
h) (CitationMode -> f CitationMode
f CitationMode
m)
instance HasCitation D.Citation where
citation :: Lens' Citation Citation
citation =
AnIso Citation Citation Citation Citation
-> Iso Citation Citation Citation Citation
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Citation Citation Citation Citation
Iso' Citation Citation
isCitation
class AsCitation a where
_Citation ::
Prism' a Citation
instance AsCitation Citation where
_Citation :: Prism' Citation Citation
_Citation =
p Citation (f Citation) -> p Citation (f Citation)
forall a. a -> a
id
instance AsCitation D.Citation where
_Citation :: Prism' Citation Citation
_Citation =
AnIso Citation Citation Citation Citation
-> Iso Citation Citation Citation Citation
forall s t a b. AnIso s t a b -> Iso b a t s
from AnIso Citation Citation Citation Citation
Iso' Citation Citation
isCitation
isCitation ::
Iso'
Citation
D.Citation
isCitation :: Iso' Citation Citation
isCitation =
(Citation -> Citation)
-> (Citation -> Citation) -> Iso' Citation Citation
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso
(\(Citation Text
i [Inline]
p [Inline]
s CitationMode
m Int
n Int
h) -> Text
-> ShortCaption
-> ShortCaption
-> CitationMode
-> Int
-> Int
-> Citation
D.Citation Text
i ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
p) ((Inline -> Inline) -> [Inline] -> ShortCaption
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Inline Inline Inline -> Inline -> Inline
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Inline Inline Inline
Iso' Inline Inline
isInline) [Inline]
s) (Getting CitationMode CitationMode CitationMode
-> CitationMode -> CitationMode
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting CitationMode CitationMode CitationMode
Iso' CitationMode CitationMode
isCitationMode CitationMode
m) Int
n Int
h)
(\(D.Citation Text
i ShortCaption
p ShortCaption
s CitationMode
m Int
n Int
h) -> Text
-> [Inline] -> [Inline] -> CitationMode -> Int -> Int -> Citation
Citation Text
i ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
p) ((Inline -> Inline) -> ShortCaption -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AReview Inline Inline -> Inline -> Inline
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Inline Inline
Iso' Inline Inline
isInline) ShortCaption
s) (AReview CitationMode CitationMode -> CitationMode -> CitationMode
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview CitationMode CitationMode
Iso' CitationMode CitationMode
isCitationMode CitationMode
m) Int
n Int
h)
instance Walkable D.Citation Citation where
walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Citation -> m Citation) -> Citation -> m Citation
walkM =
(Citation -> m Citation) -> Citation -> m Citation
Iso' Citation Citation
isCitation
query :: forall c. Monoid c => (Citation -> c) -> Citation -> c
query Citation -> c
f =
Citation -> c
f (Citation -> c) -> (Citation -> Citation) -> Citation -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Citation Citation Citation -> Citation -> Citation
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Citation Citation Citation
Iso' Citation Citation
isCitation
class HasBlocks a where
blocks ::
Lens' a [Block]
instance HasBlocks [Block] where
blocks :: Lens' [Block] [Block]
blocks =
([Block] -> f [Block]) -> [Block] -> f [Block]
forall a. a -> a
id
class AsBlocks a where
_Blocks ::
Prism' a [Block]
instance AsBlocks [Block] where
_Blocks :: Prism' [Block] [Block]
_Blocks =
p [Block] (f [Block]) -> p [Block] (f [Block])
forall a. a -> a
id
class HasInlines a where
inlines ::
Lens' a [Inline]
instance HasInlines [Inline] where
inlines :: Lens' [Inline] [Inline]
inlines =
([Inline] -> f [Inline]) -> [Inline] -> f [Inline]
forall a. a -> a
id
class AsInlines a where
_Inlines ::
Prism' a [Inline]
instance AsInlines [Inline] where
_Inlines :: Prism' [Inline] [Inline]
_Inlines =
p [Inline] (f [Inline]) -> p [Inline] (f [Inline])
forall a. a -> a
id