{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE UndecidableInstances #-}
module Text.Pandoc.Writers.AnnotatedTable
  ( toTable
  , fromTable
  , Table(..)
  , TableHead(..)
  , TableBody(..)
  , TableFoot(..)
  , HeaderRow(..)
  , BodyRow(..)
  , RowNumber(..)
  , RowHead
  , RowBody
  , Cell(..)
  , ColNumber(..)
  )
where
import           Control.Monad.RWS.Strict
import           Data.Generics                  ( Data
                                                , Typeable
                                                )
import           Data.List.NonEmpty             ( NonEmpty(..) )
import           GHC.Generics                   ( Generic )
import qualified Text.Pandoc.Builder           as B
import           Text.Pandoc.Walk               ( Walkable (..) )
data Table = Table B.Attr B.Caption [B.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, 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, 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, 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, (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)
data TableHead = TableHead B.Attr [HeaderRow]
  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, 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, 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, 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, (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)
data TableBody = TableBody B.Attr B.RowHeadColumns [HeaderRow] [BodyRow]
  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, 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, 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, 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, (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)
data  =  B.Attr [HeaderRow]
  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, 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, 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, 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, (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)
data  =  B.Attr RowNumber [Cell]
  deriving (HeaderRow -> HeaderRow -> Bool
(HeaderRow -> HeaderRow -> Bool)
-> (HeaderRow -> HeaderRow -> Bool) -> Eq HeaderRow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HeaderRow -> HeaderRow -> Bool
== :: HeaderRow -> HeaderRow -> Bool
$c/= :: HeaderRow -> HeaderRow -> Bool
/= :: HeaderRow -> HeaderRow -> Bool
Eq, Eq HeaderRow
Eq HeaderRow =>
(HeaderRow -> HeaderRow -> Ordering)
-> (HeaderRow -> HeaderRow -> Bool)
-> (HeaderRow -> HeaderRow -> Bool)
-> (HeaderRow -> HeaderRow -> Bool)
-> (HeaderRow -> HeaderRow -> Bool)
-> (HeaderRow -> HeaderRow -> HeaderRow)
-> (HeaderRow -> HeaderRow -> HeaderRow)
-> Ord HeaderRow
HeaderRow -> HeaderRow -> Bool
HeaderRow -> HeaderRow -> Ordering
HeaderRow -> HeaderRow -> HeaderRow
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 :: HeaderRow -> HeaderRow -> Ordering
compare :: HeaderRow -> HeaderRow -> Ordering
$c< :: HeaderRow -> HeaderRow -> Bool
< :: HeaderRow -> HeaderRow -> Bool
$c<= :: HeaderRow -> HeaderRow -> Bool
<= :: HeaderRow -> HeaderRow -> Bool
$c> :: HeaderRow -> HeaderRow -> Bool
> :: HeaderRow -> HeaderRow -> Bool
$c>= :: HeaderRow -> HeaderRow -> Bool
>= :: HeaderRow -> HeaderRow -> Bool
$cmax :: HeaderRow -> HeaderRow -> HeaderRow
max :: HeaderRow -> HeaderRow -> HeaderRow
$cmin :: HeaderRow -> HeaderRow -> HeaderRow
min :: HeaderRow -> HeaderRow -> HeaderRow
Ord, ReadPrec [HeaderRow]
ReadPrec HeaderRow
Int -> ReadS HeaderRow
ReadS [HeaderRow]
(Int -> ReadS HeaderRow)
-> ReadS [HeaderRow]
-> ReadPrec HeaderRow
-> ReadPrec [HeaderRow]
-> Read HeaderRow
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS HeaderRow
readsPrec :: Int -> ReadS HeaderRow
$creadList :: ReadS [HeaderRow]
readList :: ReadS [HeaderRow]
$creadPrec :: ReadPrec HeaderRow
readPrec :: ReadPrec HeaderRow
$creadListPrec :: ReadPrec [HeaderRow]
readListPrec :: ReadPrec [HeaderRow]
Read, Int -> HeaderRow -> ShowS
[HeaderRow] -> ShowS
HeaderRow -> String
(Int -> HeaderRow -> ShowS)
-> (HeaderRow -> String)
-> ([HeaderRow] -> ShowS)
-> Show HeaderRow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HeaderRow -> ShowS
showsPrec :: Int -> HeaderRow -> ShowS
$cshow :: HeaderRow -> String
show :: HeaderRow -> String
$cshowList :: [HeaderRow] -> ShowS
showList :: [HeaderRow] -> ShowS
Show, Typeable, Typeable HeaderRow
Typeable HeaderRow =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> HeaderRow -> c HeaderRow)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c HeaderRow)
-> (HeaderRow -> Constr)
-> (HeaderRow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c HeaderRow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HeaderRow))
-> ((forall b. Data b => b -> b) -> HeaderRow -> HeaderRow)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> HeaderRow -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> HeaderRow -> r)
-> (forall u. (forall d. Data d => d -> u) -> HeaderRow -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> HeaderRow -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow)
-> Data HeaderRow
HeaderRow -> Constr
HeaderRow -> DataType
(forall b. Data b => b -> b) -> HeaderRow -> HeaderRow
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) -> HeaderRow -> u
forall u. (forall d. Data d => d -> u) -> HeaderRow -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderRow -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderRow -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HeaderRow
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderRow -> c HeaderRow
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HeaderRow)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HeaderRow)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderRow -> c HeaderRow
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HeaderRow -> c HeaderRow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HeaderRow
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HeaderRow
$ctoConstr :: HeaderRow -> Constr
toConstr :: HeaderRow -> Constr
$cdataTypeOf :: HeaderRow -> DataType
dataTypeOf :: HeaderRow -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HeaderRow)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HeaderRow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HeaderRow)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HeaderRow)
$cgmapT :: (forall b. Data b => b -> b) -> HeaderRow -> HeaderRow
gmapT :: (forall b. Data b => b -> b) -> HeaderRow -> HeaderRow
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderRow -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderRow -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderRow -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HeaderRow -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HeaderRow -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> HeaderRow -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HeaderRow -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HeaderRow -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow
Data, (forall x. HeaderRow -> Rep HeaderRow x)
-> (forall x. Rep HeaderRow x -> HeaderRow) -> Generic HeaderRow
forall x. Rep HeaderRow x -> HeaderRow
forall x. HeaderRow -> Rep HeaderRow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HeaderRow -> Rep HeaderRow x
from :: forall x. HeaderRow -> Rep HeaderRow x
$cto :: forall x. Rep HeaderRow x -> HeaderRow
to :: forall x. Rep HeaderRow x -> HeaderRow
Generic)
data BodyRow = BodyRow B.Attr RowNumber RowHead RowBody
  deriving (BodyRow -> BodyRow -> Bool
(BodyRow -> BodyRow -> Bool)
-> (BodyRow -> BodyRow -> Bool) -> Eq BodyRow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BodyRow -> BodyRow -> Bool
== :: BodyRow -> BodyRow -> Bool
$c/= :: BodyRow -> BodyRow -> Bool
/= :: BodyRow -> BodyRow -> Bool
Eq, Eq BodyRow
Eq BodyRow =>
(BodyRow -> BodyRow -> Ordering)
-> (BodyRow -> BodyRow -> Bool)
-> (BodyRow -> BodyRow -> Bool)
-> (BodyRow -> BodyRow -> Bool)
-> (BodyRow -> BodyRow -> Bool)
-> (BodyRow -> BodyRow -> BodyRow)
-> (BodyRow -> BodyRow -> BodyRow)
-> Ord BodyRow
BodyRow -> BodyRow -> Bool
BodyRow -> BodyRow -> Ordering
BodyRow -> BodyRow -> BodyRow
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 :: BodyRow -> BodyRow -> Ordering
compare :: BodyRow -> BodyRow -> Ordering
$c< :: BodyRow -> BodyRow -> Bool
< :: BodyRow -> BodyRow -> Bool
$c<= :: BodyRow -> BodyRow -> Bool
<= :: BodyRow -> BodyRow -> Bool
$c> :: BodyRow -> BodyRow -> Bool
> :: BodyRow -> BodyRow -> Bool
$c>= :: BodyRow -> BodyRow -> Bool
>= :: BodyRow -> BodyRow -> Bool
$cmax :: BodyRow -> BodyRow -> BodyRow
max :: BodyRow -> BodyRow -> BodyRow
$cmin :: BodyRow -> BodyRow -> BodyRow
min :: BodyRow -> BodyRow -> BodyRow
Ord, ReadPrec [BodyRow]
ReadPrec BodyRow
Int -> ReadS BodyRow
ReadS [BodyRow]
(Int -> ReadS BodyRow)
-> ReadS [BodyRow]
-> ReadPrec BodyRow
-> ReadPrec [BodyRow]
-> Read BodyRow
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BodyRow
readsPrec :: Int -> ReadS BodyRow
$creadList :: ReadS [BodyRow]
readList :: ReadS [BodyRow]
$creadPrec :: ReadPrec BodyRow
readPrec :: ReadPrec BodyRow
$creadListPrec :: ReadPrec [BodyRow]
readListPrec :: ReadPrec [BodyRow]
Read, Int -> BodyRow -> ShowS
[BodyRow] -> ShowS
BodyRow -> String
(Int -> BodyRow -> ShowS)
-> (BodyRow -> String) -> ([BodyRow] -> ShowS) -> Show BodyRow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BodyRow -> ShowS
showsPrec :: Int -> BodyRow -> ShowS
$cshow :: BodyRow -> String
show :: BodyRow -> String
$cshowList :: [BodyRow] -> ShowS
showList :: [BodyRow] -> ShowS
Show, Typeable, Typeable BodyRow
Typeable BodyRow =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> BodyRow -> c BodyRow)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c BodyRow)
-> (BodyRow -> Constr)
-> (BodyRow -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c BodyRow))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BodyRow))
-> ((forall b. Data b => b -> b) -> BodyRow -> BodyRow)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> BodyRow -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> BodyRow -> r)
-> (forall u. (forall d. Data d => d -> u) -> BodyRow -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> BodyRow -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> BodyRow -> m BodyRow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> BodyRow -> m BodyRow)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> BodyRow -> m BodyRow)
-> Data BodyRow
BodyRow -> Constr
BodyRow -> DataType
(forall b. Data b => b -> b) -> BodyRow -> BodyRow
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) -> BodyRow -> u
forall u. (forall d. Data d => d -> u) -> BodyRow -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BodyRow -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BodyRow -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BodyRow
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BodyRow -> c BodyRow
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BodyRow)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BodyRow)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BodyRow -> c BodyRow
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BodyRow -> c BodyRow
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BodyRow
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BodyRow
$ctoConstr :: BodyRow -> Constr
toConstr :: BodyRow -> Constr
$cdataTypeOf :: BodyRow -> DataType
dataTypeOf :: BodyRow -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BodyRow)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BodyRow)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BodyRow)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BodyRow)
$cgmapT :: (forall b. Data b => b -> b) -> BodyRow -> BodyRow
gmapT :: (forall b. Data b => b -> b) -> BodyRow -> BodyRow
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BodyRow -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BodyRow -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BodyRow -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BodyRow -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BodyRow -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> BodyRow -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BodyRow -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BodyRow -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BodyRow -> m BodyRow
Data, (forall x. BodyRow -> Rep BodyRow x)
-> (forall x. Rep BodyRow x -> BodyRow) -> Generic BodyRow
forall x. Rep BodyRow x -> BodyRow
forall x. BodyRow -> Rep BodyRow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BodyRow -> Rep BodyRow x
from :: forall x. BodyRow -> Rep BodyRow x
$cto :: forall x. Rep BodyRow x -> BodyRow
to :: forall x. Rep BodyRow x -> BodyRow
Generic)
newtype RowNumber = RowNumber Int
  deriving (RowNumber -> RowNumber -> Bool
(RowNumber -> RowNumber -> Bool)
-> (RowNumber -> RowNumber -> Bool) -> Eq RowNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RowNumber -> RowNumber -> Bool
== :: RowNumber -> RowNumber -> Bool
$c/= :: RowNumber -> RowNumber -> Bool
/= :: RowNumber -> RowNumber -> Bool
Eq, Eq RowNumber
Eq RowNumber =>
(RowNumber -> RowNumber -> Ordering)
-> (RowNumber -> RowNumber -> Bool)
-> (RowNumber -> RowNumber -> Bool)
-> (RowNumber -> RowNumber -> Bool)
-> (RowNumber -> RowNumber -> Bool)
-> (RowNumber -> RowNumber -> RowNumber)
-> (RowNumber -> RowNumber -> RowNumber)
-> Ord RowNumber
RowNumber -> RowNumber -> Bool
RowNumber -> RowNumber -> Ordering
RowNumber -> RowNumber -> RowNumber
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 :: RowNumber -> RowNumber -> Ordering
compare :: RowNumber -> RowNumber -> Ordering
$c< :: RowNumber -> RowNumber -> Bool
< :: RowNumber -> RowNumber -> Bool
$c<= :: RowNumber -> RowNumber -> Bool
<= :: RowNumber -> RowNumber -> Bool
$c> :: RowNumber -> RowNumber -> Bool
> :: RowNumber -> RowNumber -> Bool
$c>= :: RowNumber -> RowNumber -> Bool
>= :: RowNumber -> RowNumber -> Bool
$cmax :: RowNumber -> RowNumber -> RowNumber
max :: RowNumber -> RowNumber -> RowNumber
$cmin :: RowNumber -> RowNumber -> RowNumber
min :: RowNumber -> RowNumber -> RowNumber
Ord, ReadPrec [RowNumber]
ReadPrec RowNumber
Int -> ReadS RowNumber
ReadS [RowNumber]
(Int -> ReadS RowNumber)
-> ReadS [RowNumber]
-> ReadPrec RowNumber
-> ReadPrec [RowNumber]
-> Read RowNumber
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RowNumber
readsPrec :: Int -> ReadS RowNumber
$creadList :: ReadS [RowNumber]
readList :: ReadS [RowNumber]
$creadPrec :: ReadPrec RowNumber
readPrec :: ReadPrec RowNumber
$creadListPrec :: ReadPrec [RowNumber]
readListPrec :: ReadPrec [RowNumber]
Read, Int -> RowNumber -> ShowS
[RowNumber] -> ShowS
RowNumber -> String
(Int -> RowNumber -> ShowS)
-> (RowNumber -> String)
-> ([RowNumber] -> ShowS)
-> Show RowNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RowNumber -> ShowS
showsPrec :: Int -> RowNumber -> ShowS
$cshow :: RowNumber -> String
show :: RowNumber -> String
$cshowList :: [RowNumber] -> ShowS
showList :: [RowNumber] -> ShowS
Show, Typeable, Typeable RowNumber
Typeable RowNumber =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> RowNumber -> c RowNumber)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c RowNumber)
-> (RowNumber -> Constr)
-> (RowNumber -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c RowNumber))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowNumber))
-> ((forall b. Data b => b -> b) -> RowNumber -> RowNumber)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> RowNumber -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> RowNumber -> r)
-> (forall u. (forall d. Data d => d -> u) -> RowNumber -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> RowNumber -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> RowNumber -> m RowNumber)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RowNumber -> m RowNumber)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> RowNumber -> m RowNumber)
-> Data RowNumber
RowNumber -> Constr
RowNumber -> DataType
(forall b. Data b => b -> b) -> RowNumber -> RowNumber
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) -> RowNumber -> u
forall u. (forall d. Data d => d -> u) -> RowNumber -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowNumber -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowNumber -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowNumber
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowNumber -> c RowNumber
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowNumber)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowNumber)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowNumber -> c RowNumber
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RowNumber -> c RowNumber
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowNumber
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RowNumber
$ctoConstr :: RowNumber -> Constr
toConstr :: RowNumber -> Constr
$cdataTypeOf :: RowNumber -> DataType
dataTypeOf :: RowNumber -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowNumber)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RowNumber)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowNumber)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowNumber)
$cgmapT :: (forall b. Data b => b -> b) -> RowNumber -> RowNumber
gmapT :: (forall b. Data b => b -> b) -> RowNumber -> RowNumber
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowNumber -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RowNumber -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowNumber -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RowNumber -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RowNumber -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RowNumber -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowNumber -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RowNumber -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RowNumber -> m RowNumber
Data, (forall x. RowNumber -> Rep RowNumber x)
-> (forall x. Rep RowNumber x -> RowNumber) -> Generic RowNumber
forall x. Rep RowNumber x -> RowNumber
forall x. RowNumber -> Rep RowNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RowNumber -> Rep RowNumber x
from :: forall x. RowNumber -> Rep RowNumber x
$cto :: forall x. Rep RowNumber x -> RowNumber
to :: forall x. Rep RowNumber x -> RowNumber
Generic, Integer -> RowNumber
RowNumber -> RowNumber
RowNumber -> RowNumber -> RowNumber
(RowNumber -> RowNumber -> RowNumber)
-> (RowNumber -> RowNumber -> RowNumber)
-> (RowNumber -> RowNumber -> RowNumber)
-> (RowNumber -> RowNumber)
-> (RowNumber -> RowNumber)
-> (RowNumber -> RowNumber)
-> (Integer -> RowNumber)
-> Num RowNumber
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: RowNumber -> RowNumber -> RowNumber
+ :: RowNumber -> RowNumber -> RowNumber
$c- :: RowNumber -> RowNumber -> RowNumber
- :: RowNumber -> RowNumber -> RowNumber
$c* :: RowNumber -> RowNumber -> RowNumber
* :: RowNumber -> RowNumber -> RowNumber
$cnegate :: RowNumber -> RowNumber
negate :: RowNumber -> RowNumber
$cabs :: RowNumber -> RowNumber
abs :: RowNumber -> RowNumber
$csignum :: RowNumber -> RowNumber
signum :: RowNumber -> RowNumber
$cfromInteger :: Integer -> RowNumber
fromInteger :: Integer -> RowNumber
Num, Int -> RowNumber
RowNumber -> Int
RowNumber -> [RowNumber]
RowNumber -> RowNumber
RowNumber -> RowNumber -> [RowNumber]
RowNumber -> RowNumber -> RowNumber -> [RowNumber]
(RowNumber -> RowNumber)
-> (RowNumber -> RowNumber)
-> (Int -> RowNumber)
-> (RowNumber -> Int)
-> (RowNumber -> [RowNumber])
-> (RowNumber -> RowNumber -> [RowNumber])
-> (RowNumber -> RowNumber -> [RowNumber])
-> (RowNumber -> RowNumber -> RowNumber -> [RowNumber])
-> Enum RowNumber
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RowNumber -> RowNumber
succ :: RowNumber -> RowNumber
$cpred :: RowNumber -> RowNumber
pred :: RowNumber -> RowNumber
$ctoEnum :: Int -> RowNumber
toEnum :: Int -> RowNumber
$cfromEnum :: RowNumber -> Int
fromEnum :: RowNumber -> Int
$cenumFrom :: RowNumber -> [RowNumber]
enumFrom :: RowNumber -> [RowNumber]
$cenumFromThen :: RowNumber -> RowNumber -> [RowNumber]
enumFromThen :: RowNumber -> RowNumber -> [RowNumber]
$cenumFromTo :: RowNumber -> RowNumber -> [RowNumber]
enumFromTo :: RowNumber -> RowNumber -> [RowNumber]
$cenumFromThenTo :: RowNumber -> RowNumber -> RowNumber -> [RowNumber]
enumFromThenTo :: RowNumber -> RowNumber -> RowNumber -> [RowNumber]
Enum)
type RowHead = [Cell]
type RowBody = [Cell]
data Cell = Cell (NonEmpty B.ColSpec) ColNumber B.Cell
  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, 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, 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, Typeable Cell
Typeable Cell =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Cell -> c Cell)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Cell)
-> (Cell -> Constr)
-> (Cell -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Cell))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell))
-> ((forall b. Data b => b -> b) -> Cell -> Cell)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r)
-> (forall u. (forall d. Data d => d -> u) -> Cell -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Cell -> m Cell)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Cell -> m Cell)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Cell -> m Cell)
-> Data Cell
Cell -> Constr
Cell -> DataType
(forall b. Data b => b -> b) -> Cell -> Cell
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u
forall u. (forall d. Data d => d -> u) -> Cell -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cell
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cell -> c Cell
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cell)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cell -> c Cell
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Cell -> c Cell
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cell
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Cell
$ctoConstr :: Cell -> Constr
toConstr :: Cell -> Constr
$cdataTypeOf :: Cell -> DataType
dataTypeOf :: Cell -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cell)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Cell)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell)
$cgmapT :: (forall b. Data b => b -> b) -> Cell -> Cell
gmapT :: (forall b. Data b => b -> b) -> Cell -> Cell
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Cell -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Cell -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Cell -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Cell -> m Cell
Data, (forall x. Cell -> Rep Cell x)
-> (forall x. Rep Cell x -> Cell) -> Generic Cell
forall x. Rep Cell x -> Cell
forall x. Cell -> Rep Cell x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Cell -> Rep Cell x
from :: forall x. Cell -> Rep Cell x
$cto :: forall x. Rep Cell x -> Cell
to :: forall x. Rep Cell x -> Cell
Generic)
newtype ColNumber = ColNumber Int
  deriving (ColNumber -> ColNumber -> Bool
(ColNumber -> ColNumber -> Bool)
-> (ColNumber -> ColNumber -> Bool) -> Eq ColNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColNumber -> ColNumber -> Bool
== :: ColNumber -> ColNumber -> Bool
$c/= :: ColNumber -> ColNumber -> Bool
/= :: ColNumber -> ColNumber -> Bool
Eq, Eq ColNumber
Eq ColNumber =>
(ColNumber -> ColNumber -> Ordering)
-> (ColNumber -> ColNumber -> Bool)
-> (ColNumber -> ColNumber -> Bool)
-> (ColNumber -> ColNumber -> Bool)
-> (ColNumber -> ColNumber -> Bool)
-> (ColNumber -> ColNumber -> ColNumber)
-> (ColNumber -> ColNumber -> ColNumber)
-> Ord ColNumber
ColNumber -> ColNumber -> Bool
ColNumber -> ColNumber -> Ordering
ColNumber -> ColNumber -> ColNumber
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 :: ColNumber -> ColNumber -> Ordering
compare :: ColNumber -> ColNumber -> Ordering
$c< :: ColNumber -> ColNumber -> Bool
< :: ColNumber -> ColNumber -> Bool
$c<= :: ColNumber -> ColNumber -> Bool
<= :: ColNumber -> ColNumber -> Bool
$c> :: ColNumber -> ColNumber -> Bool
> :: ColNumber -> ColNumber -> Bool
$c>= :: ColNumber -> ColNumber -> Bool
>= :: ColNumber -> ColNumber -> Bool
$cmax :: ColNumber -> ColNumber -> ColNumber
max :: ColNumber -> ColNumber -> ColNumber
$cmin :: ColNumber -> ColNumber -> ColNumber
min :: ColNumber -> ColNumber -> ColNumber
Ord, ReadPrec [ColNumber]
ReadPrec ColNumber
Int -> ReadS ColNumber
ReadS [ColNumber]
(Int -> ReadS ColNumber)
-> ReadS [ColNumber]
-> ReadPrec ColNumber
-> ReadPrec [ColNumber]
-> Read ColNumber
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColNumber
readsPrec :: Int -> ReadS ColNumber
$creadList :: ReadS [ColNumber]
readList :: ReadS [ColNumber]
$creadPrec :: ReadPrec ColNumber
readPrec :: ReadPrec ColNumber
$creadListPrec :: ReadPrec [ColNumber]
readListPrec :: ReadPrec [ColNumber]
Read, Int -> ColNumber -> ShowS
[ColNumber] -> ShowS
ColNumber -> String
(Int -> ColNumber -> ShowS)
-> (ColNumber -> String)
-> ([ColNumber] -> ShowS)
-> Show ColNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColNumber -> ShowS
showsPrec :: Int -> ColNumber -> ShowS
$cshow :: ColNumber -> String
show :: ColNumber -> String
$cshowList :: [ColNumber] -> ShowS
showList :: [ColNumber] -> ShowS
Show, Typeable, Typeable ColNumber
Typeable ColNumber =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> ColNumber -> c ColNumber)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ColNumber)
-> (ColNumber -> Constr)
-> (ColNumber -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ColNumber))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColNumber))
-> ((forall b. Data b => b -> b) -> ColNumber -> ColNumber)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> ColNumber -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> ColNumber -> r)
-> (forall u. (forall d. Data d => d -> u) -> ColNumber -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> ColNumber -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ColNumber -> m ColNumber)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ColNumber -> m ColNumber)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ColNumber -> m ColNumber)
-> Data ColNumber
ColNumber -> Constr
ColNumber -> DataType
(forall b. Data b => b -> b) -> ColNumber -> ColNumber
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) -> ColNumber -> u
forall u. (forall d. Data d => d -> u) -> ColNumber -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColNumber -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColNumber -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColNumber
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColNumber -> c ColNumber
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColNumber)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColNumber)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColNumber -> c ColNumber
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ColNumber -> c ColNumber
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColNumber
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ColNumber
$ctoConstr :: ColNumber -> Constr
toConstr :: ColNumber -> Constr
$cdataTypeOf :: ColNumber -> DataType
dataTypeOf :: ColNumber -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColNumber)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ColNumber)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColNumber)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColNumber)
$cgmapT :: (forall b. Data b => b -> b) -> ColNumber -> ColNumber
gmapT :: (forall b. Data b => b -> b) -> ColNumber -> ColNumber
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColNumber -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ColNumber -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColNumber -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ColNumber -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ColNumber -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ColNumber -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColNumber -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ColNumber -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ColNumber -> m ColNumber
Data, (forall x. ColNumber -> Rep ColNumber x)
-> (forall x. Rep ColNumber x -> ColNumber) -> Generic ColNumber
forall x. Rep ColNumber x -> ColNumber
forall x. ColNumber -> Rep ColNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColNumber -> Rep ColNumber x
from :: forall x. ColNumber -> Rep ColNumber x
$cto :: forall x. Rep ColNumber x -> ColNumber
to :: forall x. Rep ColNumber x -> ColNumber
Generic, Integer -> ColNumber
ColNumber -> ColNumber
ColNumber -> ColNumber -> ColNumber
(ColNumber -> ColNumber -> ColNumber)
-> (ColNumber -> ColNumber -> ColNumber)
-> (ColNumber -> ColNumber -> ColNumber)
-> (ColNumber -> ColNumber)
-> (ColNumber -> ColNumber)
-> (ColNumber -> ColNumber)
-> (Integer -> ColNumber)
-> Num ColNumber
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: ColNumber -> ColNumber -> ColNumber
+ :: ColNumber -> ColNumber -> ColNumber
$c- :: ColNumber -> ColNumber -> ColNumber
- :: ColNumber -> ColNumber -> ColNumber
$c* :: ColNumber -> ColNumber -> ColNumber
* :: ColNumber -> ColNumber -> ColNumber
$cnegate :: ColNumber -> ColNumber
negate :: ColNumber -> ColNumber
$cabs :: ColNumber -> ColNumber
abs :: ColNumber -> ColNumber
$csignum :: ColNumber -> ColNumber
signum :: ColNumber -> ColNumber
$cfromInteger :: Integer -> ColNumber
fromInteger :: Integer -> ColNumber
Num, Int -> ColNumber
ColNumber -> Int
ColNumber -> [ColNumber]
ColNumber -> ColNumber
ColNumber -> ColNumber -> [ColNumber]
ColNumber -> ColNumber -> ColNumber -> [ColNumber]
(ColNumber -> ColNumber)
-> (ColNumber -> ColNumber)
-> (Int -> ColNumber)
-> (ColNumber -> Int)
-> (ColNumber -> [ColNumber])
-> (ColNumber -> ColNumber -> [ColNumber])
-> (ColNumber -> ColNumber -> [ColNumber])
-> (ColNumber -> ColNumber -> ColNumber -> [ColNumber])
-> Enum ColNumber
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ColNumber -> ColNumber
succ :: ColNumber -> ColNumber
$cpred :: ColNumber -> ColNumber
pred :: ColNumber -> ColNumber
$ctoEnum :: Int -> ColNumber
toEnum :: Int -> ColNumber
$cfromEnum :: ColNumber -> Int
fromEnum :: ColNumber -> Int
$cenumFrom :: ColNumber -> [ColNumber]
enumFrom :: ColNumber -> [ColNumber]
$cenumFromThen :: ColNumber -> ColNumber -> [ColNumber]
enumFromThen :: ColNumber -> ColNumber -> [ColNumber]
$cenumFromTo :: ColNumber -> ColNumber -> [ColNumber]
enumFromTo :: ColNumber -> ColNumber -> [ColNumber]
$cenumFromThenTo :: ColNumber -> ColNumber -> ColNumber -> [ColNumber]
enumFromThenTo :: ColNumber -> ColNumber -> ColNumber -> [ColNumber]
Enum)
toTable
  :: B.Attr
  -> B.Caption
  -> [B.ColSpec]
  -> B.TableHead
  -> [B.TableBody]
  -> B.TableFoot
  -> Table
toTable :: Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
toTable Attr
attr Caption
cap [ColSpec]
cs TableHead
th [TableBody]
tbs TableFoot
tf = Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Table
Table Attr
attr Caption
cap [ColSpec]
cs TableHead
th' [TableBody]
tbs' TableFoot
tf'
 where
  (TableHead
th', [TableBody]
tbs', TableFoot
tf') = ((TableHead, [TableBody], TableFoot), ())
-> (TableHead, [TableBody], TableFoot)
forall a b. (a, b) -> a
fst (((TableHead, [TableBody], TableFoot), ())
 -> (TableHead, [TableBody], TableFoot))
-> ((TableHead, [TableBody], TableFoot), ())
-> (TableHead, [TableBody], TableFoot)
forall a b. (a -> b) -> a -> b
$ RWS
  ([ColSpec], Int) () RowNumber (TableHead, [TableBody], TableFoot)
-> ([ColSpec], Int)
-> RowNumber
-> ((TableHead, [TableBody], TableFoot), ())
forall r w s a. RWS r w s a -> r -> s -> (a, w)
evalRWS (TableHead
-> [TableBody]
-> TableFoot
-> RWS
     ([ColSpec], Int) () RowNumber (TableHead, [TableBody], TableFoot)
annotateTable TableHead
th [TableBody]
tbs TableFoot
tf) ([ColSpec]
cs, [ColSpec] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ColSpec]
cs) RowNumber
0
type AnnM a = RWS ([B.ColSpec], Int) () RowNumber a
incRowNumber :: AnnM RowNumber
incRowNumber :: AnnM RowNumber
incRowNumber = do
  RowNumber
rn <- AnnM RowNumber
forall s (m :: * -> *). MonadState s m => m s
get
  RowNumber -> RWST ([ColSpec], Int) () RowNumber Identity ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (RowNumber -> RWST ([ColSpec], Int) () RowNumber Identity ())
-> RowNumber -> RWST ([ColSpec], Int) () RowNumber Identity ()
forall a b. (a -> b) -> a -> b
$ RowNumber
rn RowNumber -> RowNumber -> RowNumber
forall a. Num a => a -> a -> a
+ RowNumber
1
  RowNumber -> AnnM RowNumber
forall a. a -> RWST ([ColSpec], Int) () RowNumber Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return RowNumber
rn
annotateTable
  :: B.TableHead
  -> [B.TableBody]
  -> B.TableFoot
  -> AnnM (TableHead, [TableBody], TableFoot)
annotateTable :: TableHead
-> [TableBody]
-> TableFoot
-> RWS
     ([ColSpec], Int) () RowNumber (TableHead, [TableBody], TableFoot)
annotateTable TableHead
th [TableBody]
tbs TableFoot
tf = do
  TableHead
th'  <- TableHead -> AnnM TableHead
annotateTableHead TableHead
th
  [TableBody]
tbs' <- (TableBody
 -> RWST ([ColSpec], Int) () RowNumber Identity TableBody)
-> [TableBody]
-> RWST ([ColSpec], Int) () RowNumber Identity [TableBody]
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 TableBody -> RWST ([ColSpec], Int) () RowNumber Identity TableBody
annotateTableBody [TableBody]
tbs
  TableFoot
tf'  <- TableFoot -> AnnM TableFoot
annotateTableFoot TableFoot
tf
  (TableHead, [TableBody], TableFoot)
-> RWS
     ([ColSpec], Int) () RowNumber (TableHead, [TableBody], TableFoot)
forall a. a -> RWST ([ColSpec], Int) () RowNumber Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableHead
th', [TableBody]
tbs', TableFoot
tf')
annotateTableHead :: B.TableHead -> AnnM TableHead
annotateTableHead :: TableHead -> AnnM TableHead
annotateTableHead (B.TableHead Attr
attr [Row]
rows) =
  Attr -> [HeaderRow] -> TableHead
TableHead Attr
attr ([HeaderRow] -> TableHead)
-> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
-> AnnM TableHead
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Row] -> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
annotateHeaderSection [Row]
rows
annotateTableBody :: B.TableBody -> AnnM TableBody
annotateTableBody :: TableBody -> RWST ([ColSpec], Int) () RowNumber Identity TableBody
annotateTableBody (B.TableBody Attr
attr RowHeadColumns
rhc [Row]
th [Row]
tb) = do
  Int
twidth <- (([ColSpec], Int) -> Int)
-> RWST ([ColSpec], Int) () RowNumber Identity Int
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ([ColSpec], Int) -> Int
forall a b. (a, b) -> b
snd
  let rhc' :: RowHeadColumns
rhc' = RowHeadColumns -> RowHeadColumns -> RowHeadColumns
forall a. Ord a => a -> a -> a
max RowHeadColumns
0 (RowHeadColumns -> RowHeadColumns)
-> RowHeadColumns -> RowHeadColumns
forall a b. (a -> b) -> a -> b
$ RowHeadColumns -> RowHeadColumns -> RowHeadColumns
forall a. Ord a => a -> a -> a
min (Int -> RowHeadColumns
B.RowHeadColumns Int
twidth) RowHeadColumns
rhc
  [HeaderRow]
th' <- [Row] -> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
annotateHeaderSection [Row]
th
  [BodyRow]
tb' <- RowHeadColumns -> [Row] -> AnnM [BodyRow]
annotateBodySection RowHeadColumns
rhc' [Row]
tb
  TableBody -> RWST ([ColSpec], Int) () RowNumber Identity TableBody
forall a. a -> RWST ([ColSpec], Int) () RowNumber Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableBody
 -> RWST ([ColSpec], Int) () RowNumber Identity TableBody)
-> TableBody
-> RWST ([ColSpec], Int) () RowNumber Identity TableBody
forall a b. (a -> b) -> a -> b
$ Attr -> RowHeadColumns -> [HeaderRow] -> [BodyRow] -> TableBody
TableBody Attr
attr RowHeadColumns
rhc' [HeaderRow]
th' [BodyRow]
tb'
annotateTableFoot :: B.TableFoot -> AnnM TableFoot
 (B.TableFoot Attr
attr [Row]
rows) =
  Attr -> [HeaderRow] -> TableFoot
TableFoot Attr
attr ([HeaderRow] -> TableFoot)
-> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
-> AnnM TableFoot
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Row] -> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
annotateHeaderSection [Row]
rows
annotateHeaderSection :: [B.Row] -> AnnM [HeaderRow]
 [Row]
rows = do
  [ColSpec]
colspec <- (([ColSpec], Int) -> [ColSpec])
-> RWST ([ColSpec], Int) () RowNumber Identity [ColSpec]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ([ColSpec], Int) -> [ColSpec]
forall a b. (a, b) -> a
fst
  let hangcolspec :: [(RowSpan, ColSpec)]
hangcolspec = (RowSpan
1, ) (ColSpec -> (RowSpan, ColSpec))
-> [ColSpec] -> [(RowSpan, ColSpec)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ColSpec]
colspec
  [(RowSpan, ColSpec)]
-> ([HeaderRow] -> [HeaderRow])
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
forall {b}.
[(RowSpan, ColSpec)]
-> ([HeaderRow] -> b)
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity b
annotateHeaderSection' [(RowSpan, ColSpec)]
hangcolspec [HeaderRow] -> [HeaderRow]
forall a. a -> a
id ([Row] -> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow])
-> [Row] -> RWST ([ColSpec], Int) () RowNumber Identity [HeaderRow]
forall a b. (a -> b) -> a -> b
$ [Row] -> [Row]
B.clipRows [Row]
rows
 where
  annotateHeaderSection' :: [(RowSpan, ColSpec)]
-> ([HeaderRow] -> b)
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity b
annotateHeaderSection' [(RowSpan, ColSpec)]
oldHang [HeaderRow] -> b
acc (B.Row Attr
attr [Cell]
cells : [Row]
rs) = do
    let (ColNumber
_, [(RowSpan, ColSpec)]
newHang, [Cell]
cells', [Cell]
_) =
          ColNumber
-> [(RowSpan, ColSpec)]
-> [Cell]
-> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
annotateRowSection ColNumber
0 [(RowSpan, ColSpec)]
oldHang ([Cell] -> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell]))
-> [Cell] -> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
forall a b. (a -> b) -> a -> b
$ [Cell]
cells [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> Cell -> [Cell]
forall a. a -> [a]
repeat Cell
B.emptyCell
    RowNumber
n <- AnnM RowNumber
incRowNumber
    let annRow :: HeaderRow
annRow = Attr -> RowNumber -> [Cell] -> HeaderRow
HeaderRow Attr
attr RowNumber
n [Cell]
cells'
    [(RowSpan, ColSpec)]
-> ([HeaderRow] -> b)
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity b
annotateHeaderSection' [(RowSpan, ColSpec)]
newHang ([HeaderRow] -> b
acc ([HeaderRow] -> b)
-> ([HeaderRow] -> [HeaderRow]) -> [HeaderRow] -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HeaderRow
annRow HeaderRow -> [HeaderRow] -> [HeaderRow]
forall a. a -> [a] -> [a]
:)) [Row]
rs
  annotateHeaderSection' [(RowSpan, ColSpec)]
_ [HeaderRow] -> b
acc [] = b -> RWST ([ColSpec], Int) () RowNumber Identity b
forall a. a -> RWST ([ColSpec], Int) () RowNumber Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> RWST ([ColSpec], Int) () RowNumber Identity b)
-> b -> RWST ([ColSpec], Int) () RowNumber Identity b
forall a b. (a -> b) -> a -> b
$ [HeaderRow] -> b
acc []
annotateBodySection :: B.RowHeadColumns -> [B.Row] -> AnnM [BodyRow]
annotateBodySection :: RowHeadColumns -> [Row] -> AnnM [BodyRow]
annotateBodySection (B.RowHeadColumns Int
rhc) [Row]
rows = do
  [ColSpec]
colspec <- (([ColSpec], Int) -> [ColSpec])
-> RWST ([ColSpec], Int) () RowNumber Identity [ColSpec]
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks ([ColSpec], Int) -> [ColSpec]
forall a b. (a, b) -> a
fst
  let colspec' :: [(RowSpan, ColSpec)]
colspec'             = (RowSpan
1, ) (ColSpec -> (RowSpan, ColSpec))
-> [ColSpec] -> [(RowSpan, ColSpec)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ColSpec]
colspec
  let ([(RowSpan, ColSpec)]
stubspec, [(RowSpan, ColSpec)]
bodyspec) = Int
-> [(RowSpan, ColSpec)]
-> ([(RowSpan, ColSpec)], [(RowSpan, ColSpec)])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
rhc [(RowSpan, ColSpec)]
colspec'
  [(RowSpan, ColSpec)]
-> [(RowSpan, ColSpec)]
-> ([BodyRow] -> [BodyRow])
-> [Row]
-> AnnM [BodyRow]
forall {b}.
[(RowSpan, ColSpec)]
-> [(RowSpan, ColSpec)]
-> ([BodyRow] -> b)
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity b
normalizeBodySection' [(RowSpan, ColSpec)]
stubspec [(RowSpan, ColSpec)]
bodyspec [BodyRow] -> [BodyRow]
forall a. a -> a
id ([Row] -> AnnM [BodyRow]) -> [Row] -> AnnM [BodyRow]
forall a b. (a -> b) -> a -> b
$ [Row] -> [Row]
B.clipRows [Row]
rows
 where
  normalizeBodySection' :: [(RowSpan, ColSpec)]
-> [(RowSpan, ColSpec)]
-> ([BodyRow] -> b)
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity b
normalizeBodySection' [(RowSpan, ColSpec)]
headHang [(RowSpan, ColSpec)]
bodyHang [BodyRow] -> b
acc (B.Row Attr
attr [Cell]
cells : [Row]
rs) = do
    let (ColNumber
colnum, [(RowSpan, ColSpec)]
headHang', [Cell]
rowStub, [Cell]
cells') =
          ColNumber
-> [(RowSpan, ColSpec)]
-> [Cell]
-> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
annotateRowSection ColNumber
0 [(RowSpan, ColSpec)]
headHang ([Cell] -> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell]))
-> [Cell] -> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
forall a b. (a -> b) -> a -> b
$ [Cell]
cells [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> Cell -> [Cell]
forall a. a -> [a]
repeat Cell
B.emptyCell
    let (ColNumber
_, [(RowSpan, ColSpec)]
bodyHang', [Cell]
rowBody, [Cell]
_) = ColNumber
-> [(RowSpan, ColSpec)]
-> [Cell]
-> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
annotateRowSection ColNumber
colnum [(RowSpan, ColSpec)]
bodyHang [Cell]
cells'
    RowNumber
n <- AnnM RowNumber
incRowNumber
    let annRow :: BodyRow
annRow = Attr -> RowNumber -> [Cell] -> [Cell] -> BodyRow
BodyRow Attr
attr RowNumber
n [Cell]
rowStub [Cell]
rowBody
    [(RowSpan, ColSpec)]
-> [(RowSpan, ColSpec)]
-> ([BodyRow] -> b)
-> [Row]
-> RWST ([ColSpec], Int) () RowNumber Identity b
normalizeBodySection' [(RowSpan, ColSpec)]
headHang' [(RowSpan, ColSpec)]
bodyHang' ([BodyRow] -> b
acc ([BodyRow] -> b) -> ([BodyRow] -> [BodyRow]) -> [BodyRow] -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BodyRow
annRow BodyRow -> [BodyRow] -> [BodyRow]
forall a. a -> [a] -> [a]
:)) [Row]
rs
  normalizeBodySection' [(RowSpan, ColSpec)]
_ [(RowSpan, ColSpec)]
_ [BodyRow] -> b
acc [] = b -> RWST ([ColSpec], Int) () RowNumber Identity b
forall a. a -> RWST ([ColSpec], Int) () RowNumber Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> RWST ([ColSpec], Int) () RowNumber Identity b)
-> b -> RWST ([ColSpec], Int) () RowNumber Identity b
forall a b. (a -> b) -> a -> b
$ [BodyRow] -> b
acc []
annotateRowSection
  :: ColNumber 
  -> [(B.RowSpan, B.ColSpec)] 
                              
  -> [B.Cell] 
  -> (ColNumber, [(B.RowSpan, B.ColSpec)], [Cell], [B.Cell]) 
                                                             
                                                             
                                                             
                                                             
                                                             
                                                             
                                                             
                                                             
annotateRowSection :: ColNumber
-> [(RowSpan, ColSpec)]
-> [Cell]
-> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
annotateRowSection !ColNumber
colnum [(RowSpan, ColSpec)]
oldHang [Cell]
cells
  
  
  | (RowSpan
o, ColSpec
colspec) : [(RowSpan, ColSpec)]
os <- [(RowSpan, ColSpec)]
oldHang
  , RowSpan
o RowSpan -> RowSpan -> Bool
forall a. Ord a => a -> a -> Bool
> RowSpan
1
  = let (ColNumber
colnum', [(RowSpan, ColSpec)]
newHang, [Cell]
newCell, [Cell]
cells') =
            ColNumber
-> [(RowSpan, ColSpec)]
-> [Cell]
-> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
annotateRowSection (ColNumber
colnum ColNumber -> ColNumber -> ColNumber
forall a. Num a => a -> a -> a
+ ColNumber
1) [(RowSpan, ColSpec)]
os [Cell]
cells
    in  (ColNumber
colnum', (RowSpan
o RowSpan -> RowSpan -> RowSpan
forall a. Num a => a -> a -> a
- RowSpan
1, ColSpec
colspec) (RowSpan, ColSpec) -> [(RowSpan, ColSpec)] -> [(RowSpan, ColSpec)]
forall a. a -> [a] -> [a]
: [(RowSpan, ColSpec)]
newHang, [Cell]
newCell, [Cell]
cells')
  
  
  | Cell
c : [Cell]
cells' <- [Cell]
cells
  , (RowSpan
h, ColSpan
w) <- Cell -> (RowSpan, ColSpan)
getDim Cell
c
  , ColSpan
w' <- ColSpan -> ColSpan -> ColSpan
forall a. Ord a => a -> a -> a
max ColSpan
1 ColSpan
w
  , (ColSpan
w'', cellHang :: [(RowSpan, ColSpec)]
cellHang@((RowSpan, ColSpec)
chStart : [(RowSpan, ColSpec)]
chRest), [(RowSpan, ColSpec)]
oldHang') <- RowSpan
-> ColSpan
-> [(RowSpan, ColSpec)]
-> (ColSpan, [(RowSpan, ColSpec)], [(RowSpan, ColSpec)])
splitCellHang RowSpan
h ColSpan
w' [(RowSpan, ColSpec)]
oldHang
  = let c' :: Cell
c'      = ColSpan -> Cell -> Cell
setW ColSpan
w'' Cell
c
        annCell :: Cell
annCell = NonEmpty ColSpec -> ColNumber -> Cell -> Cell
Cell ((RowSpan, ColSpec) -> ColSpec
forall a b. (a, b) -> b
snd ((RowSpan, ColSpec) -> ColSpec)
-> NonEmpty (RowSpan, ColSpec) -> NonEmpty ColSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (RowSpan, ColSpec)
chStart (RowSpan, ColSpec)
-> [(RowSpan, ColSpec)] -> NonEmpty (RowSpan, ColSpec)
forall a. a -> [a] -> NonEmpty a
:| [(RowSpan, ColSpec)]
chRest) ColNumber
colnum Cell
c'
        colnum' :: ColNumber
colnum' = ColNumber
colnum ColNumber -> ColNumber -> ColNumber
forall a. Num a => a -> a -> a
+ Int -> ColNumber
ColNumber (ColSpan -> Int
getColSpan ColSpan
w'')
        (ColNumber
colnum'', [(RowSpan, ColSpec)]
newHang, [Cell]
newCells, [Cell]
remainCells) =
            ColNumber
-> [(RowSpan, ColSpec)]
-> [Cell]
-> (ColNumber, [(RowSpan, ColSpec)], [Cell], [Cell])
annotateRowSection ColNumber
colnum' [(RowSpan, ColSpec)]
oldHang' [Cell]
cells'
    in  (ColNumber
colnum'', [(RowSpan, ColSpec)]
cellHang [(RowSpan, ColSpec)]
-> [(RowSpan, ColSpec)] -> [(RowSpan, ColSpec)]
forall a. Semigroup a => a -> a -> a
<> [(RowSpan, ColSpec)]
newHang, Cell
annCell Cell -> [Cell] -> [Cell]
forall a. a -> [a] -> [a]
: [Cell]
newCells, [Cell]
remainCells)
  
  | Bool
otherwise
  = (ColNumber
colnum, [], [], [Cell]
cells)
 where
  getColSpan :: ColSpan -> Int
getColSpan (B.ColSpan Int
x) = Int
x
  getDim :: Cell -> (RowSpan, ColSpan)
getDim (B.Cell Attr
_ Alignment
_ RowSpan
h ColSpan
w [Block]
_) = (RowSpan
h, ColSpan
w)
  setW :: ColSpan -> Cell -> Cell
setW ColSpan
w (B.Cell Attr
a Alignment
b RowSpan
h ColSpan
_ [Block]
c) = Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
B.Cell Attr
a Alignment
b RowSpan
h ColSpan
w [Block]
c
splitCellHang
  :: B.RowSpan
  -> B.ColSpan
  -> [(B.RowSpan, B.ColSpec)]
  -> (B.ColSpan, [(B.RowSpan, B.ColSpec)], [(B.RowSpan, B.ColSpec)])
splitCellHang :: RowSpan
-> ColSpan
-> [(RowSpan, ColSpec)]
-> (ColSpan, [(RowSpan, ColSpec)], [(RowSpan, ColSpec)])
splitCellHang RowSpan
h ColSpan
n = ColSpan
-> [(RowSpan, ColSpec)]
-> (ColSpan, [(RowSpan, ColSpec)], [(RowSpan, ColSpec)])
forall {a} {b}.
(Eq a, Num a) =>
ColSpan -> [(a, b)] -> (ColSpan, [(RowSpan, b)], [(a, b)])
go ColSpan
0
 where
  go :: ColSpan -> [(a, b)] -> (ColSpan, [(RowSpan, b)], [(a, b)])
go ColSpan
acc ((a
1, b
spec) : [(a, b)]
ls) | ColSpan
acc ColSpan -> ColSpan -> Bool
forall a. Ord a => a -> a -> Bool
< ColSpan
n =
    let (ColSpan
acc', [(RowSpan, b)]
hang, [(a, b)]
ls') = ColSpan -> [(a, b)] -> (ColSpan, [(RowSpan, b)], [(a, b)])
go (ColSpan
acc ColSpan -> ColSpan -> ColSpan
forall a. Num a => a -> a -> a
+ ColSpan
1) [(a, b)]
ls in (ColSpan
acc', (RowSpan
h, b
spec) (RowSpan, b) -> [(RowSpan, b)] -> [(RowSpan, b)]
forall a. a -> [a] -> [a]
: [(RowSpan, b)]
hang, [(a, b)]
ls')
  go ColSpan
acc [(a, b)]
l = (ColSpan
acc, [], [(a, b)]
l)
fromTable
  :: Table
  -> ( B.Attr
     , B.Caption
     , [B.ColSpec]
     , B.TableHead
     , [B.TableBody]
     , B.TableFoot
     )
fromTable :: Table
-> (Attr, Caption, [ColSpec], TableHead, [TableBody], TableFoot)
fromTable (Table Attr
attr Caption
cap [ColSpec]
cs TableHead
th [TableBody]
tbs TableFoot
tf) = (Attr
attr, Caption
cap, [ColSpec]
cs, TableHead
th', [TableBody]
tbs', TableFoot
tf')
 where
  th' :: TableHead
th'  = TableHead -> TableHead
fromTableHead TableHead
th
  tbs' :: [TableBody]
tbs' = (TableBody -> TableBody) -> [TableBody] -> [TableBody]
forall a b. (a -> b) -> [a] -> [b]
map TableBody -> TableBody
fromTableBody [TableBody]
tbs
  tf' :: TableFoot
tf'  = TableFoot -> TableFoot
fromTableFoot TableFoot
tf
fromTableHead :: TableHead -> B.TableHead
fromTableHead :: TableHead -> TableHead
fromTableHead (TableHead Attr
attr [HeaderRow]
rows) = Attr -> [Row] -> TableHead
B.TableHead Attr
attr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ HeaderRow -> Row
fromHeaderRow (HeaderRow -> Row) -> [HeaderRow] -> [Row]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [HeaderRow]
rows
fromTableBody :: TableBody -> B.TableBody
fromTableBody :: TableBody -> TableBody
fromTableBody (TableBody Attr
attr RowHeadColumns
rhc [HeaderRow]
th [BodyRow]
tb) =
  Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
B.TableBody Attr
attr RowHeadColumns
rhc (HeaderRow -> Row
fromHeaderRow (HeaderRow -> Row) -> [HeaderRow] -> [Row]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [HeaderRow]
th) (BodyRow -> Row
fromBodyRow (BodyRow -> Row) -> [BodyRow] -> [Row]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BodyRow]
tb)
fromTableFoot :: TableFoot -> B.TableFoot
 (TableFoot Attr
attr [HeaderRow]
rows) = Attr -> [Row] -> TableFoot
B.TableFoot Attr
attr ([Row] -> TableFoot) -> [Row] -> TableFoot
forall a b. (a -> b) -> a -> b
$ HeaderRow -> Row
fromHeaderRow (HeaderRow -> Row) -> [HeaderRow] -> [Row]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [HeaderRow]
rows
fromHeaderRow :: HeaderRow -> B.Row
 (HeaderRow Attr
attr RowNumber
_ [Cell]
cells) = Attr -> [Cell] -> Row
B.Row Attr
attr ([Cell] -> Row) -> [Cell] -> Row
forall a b. (a -> b) -> a -> b
$ Cell -> Cell
fromCell (Cell -> Cell) -> [Cell] -> [Cell]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Cell]
cells
fromBodyRow :: BodyRow -> B.Row
fromBodyRow :: BodyRow -> Row
fromBodyRow (BodyRow Attr
attr RowNumber
_ [Cell]
rh [Cell]
rb) =
  Attr -> [Cell] -> Row
B.Row Attr
attr ((Cell -> Cell
fromCell (Cell -> Cell) -> [Cell] -> [Cell]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Cell]
rh) [Cell] -> [Cell] -> [Cell]
forall a. Semigroup a => a -> a -> a
<> (Cell -> Cell
fromCell (Cell -> Cell) -> [Cell] -> [Cell]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Cell]
rb))
fromCell :: Cell -> B.Cell
fromCell :: Cell -> Cell
fromCell (Cell NonEmpty ColSpec
_ ColNumber
_ Cell
c) = Cell
c
instance Walkable a B.Cell => Walkable a Cell where
  walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(a -> m a) -> Cell -> m Cell
walkM a -> m a
f (Cell NonEmpty ColSpec
colspecs ColNumber
colnum Cell
cell) =
    NonEmpty ColSpec -> ColNumber -> Cell -> Cell
Cell NonEmpty ColSpec
colspecs ColNumber
colnum (Cell -> Cell) -> m Cell -> m Cell
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m a) -> Cell -> m Cell
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(a -> m a) -> Cell -> m Cell
walkM a -> m a
f Cell
cell
  query :: forall c. Monoid c => (a -> c) -> Cell -> c
query a -> c
f (Cell NonEmpty ColSpec
_colspecs ColNumber
_colnum Cell
cell) = (a -> c) -> Cell -> c
forall c. Monoid c => (a -> c) -> Cell -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query a -> c
f Cell
cell
instance Walkable a B.Cell => Walkable a HeaderRow where
  walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(a -> m a) -> HeaderRow -> m HeaderRow
walkM a -> m a
f (HeaderRow Attr
attr RowNumber
rownum [Cell]
cells) =
    Attr -> RowNumber -> [Cell] -> HeaderRow
HeaderRow Attr
attr RowNumber
rownum ([Cell] -> HeaderRow) -> m [Cell] -> m HeaderRow
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m a) -> [Cell] -> m [Cell]
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(a -> m a) -> [Cell] -> m [Cell]
walkM a -> m a
f [Cell]
cells
  query :: forall c. Monoid c => (a -> c) -> HeaderRow -> c
query a -> c
f (HeaderRow Attr
_attr RowNumber
_rownum [Cell]
cells) = (a -> c) -> [Cell] -> c
forall c. Monoid c => (a -> c) -> [Cell] -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query a -> c
f [Cell]
cells
instance Walkable a B.Cell => Walkable a TableHead where
  walkM :: forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(a -> m a) -> TableHead -> m TableHead
walkM a -> m a
f (TableHead Attr
attr [HeaderRow]
rows) =
    Attr -> [HeaderRow] -> TableHead
TableHead Attr
attr ([HeaderRow] -> TableHead) -> m [HeaderRow] -> m TableHead
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> m a) -> [HeaderRow] -> m [HeaderRow]
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(a -> m a) -> [HeaderRow] -> m [HeaderRow]
walkM a -> m a
f [HeaderRow]
rows
  query :: forall c. Monoid c => (a -> c) -> TableHead -> c
query a -> c
f (TableHead Attr
_attr [HeaderRow]
rows) = (a -> c) -> [HeaderRow] -> c
forall c. Monoid c => (a -> c) -> [HeaderRow] -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query a -> c
f [HeaderRow]
rows