{-# LANGUAGE RecordWildCards #-}
module Text.Layout.Table.Style
(
asciiS
, asciiRoundS
, asciiDoubleS
, unicodeS
, unicodeBoldHeaderS
, unicodeRoundS
, unicodeBoldS
, unicodeBoldStripedS
, unicodeDoubleFrameS
, withoutBorders
, withoutTopBorder
, withoutBottomBorder
, withoutLeftBorder
, withoutRightBorder
, withRoundCorners
, inheritStyle
, inheritStyleHeaderGroup
, asciiTableStyleFromSpec
, roundedAsciiTableStyleFromSpec
, unicodeTableStyleFromSpec
, tableStyleFromSpec
, TableStyleSpec(..)
, simpleTableStyleSpec
, setTableStyleSpecSeparator
, TableStyle(..)
) where
import Text.Layout.Table.LineStyle
data TableStyle rowSep colSep
= TableStyle
{ :: String
, :: String
, :: String
, :: colSep -> colSep -> String
, :: String
, :: String
, :: String
, :: colSep -> String
, :: String
, :: String
, :: colSep -> String
, :: String
, :: String
, :: String
, :: rowSep -> rowSep -> String
, :: String
, :: String
, :: String
, :: rowSep -> String
, :: String
, :: String
, :: rowSep -> String
, :: String
, :: String
, :: String
, :: String
, :: String
, :: String
, :: String
, :: String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupL :: String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupR :: String
, forall rowSep colSep. TableStyle rowSep colSep -> colSep -> String
groupC :: colSep -> String
, forall rowSep colSep. TableStyle rowSep colSep -> rowSep -> String
groupSepH :: rowSep -> String
, forall rowSep colSep.
TableStyle rowSep colSep -> rowSep -> colSep -> String
groupSepC :: rowSep -> colSep -> String
, forall rowSep colSep. TableStyle rowSep colSep -> rowSep -> String
groupSepLC :: rowSep -> String
, forall rowSep colSep. TableStyle rowSep colSep -> rowSep -> String
groupSepRC :: rowSep -> String
, forall rowSep colSep. TableStyle rowSep colSep -> colSep -> String
groupTopC :: colSep -> String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupTopL :: String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupTopR :: String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupTopH :: String
, forall rowSep colSep. TableStyle rowSep colSep -> colSep -> String
groupBottomC :: colSep -> String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupBottomL :: String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupBottomR :: String
, forall rowSep colSep. TableStyle rowSep colSep -> String
groupBottomH :: String
}
inheritStyle :: (c -> a)
-> (d -> b)
-> TableStyle a b
-> TableStyle c d
inheritStyle :: forall c a d b.
(c -> a) -> (d -> b) -> TableStyle a b -> TableStyle c d
inheritStyle c -> a
f d -> b
g = (c -> a)
-> (c -> a)
-> (d -> b)
-> (d -> b)
-> TableStyle a b
-> TableStyle c d
forall c a d b.
(c -> a)
-> (c -> a)
-> (d -> b)
-> (d -> b)
-> TableStyle a b
-> TableStyle c d
inheritStyleHeaderGroup c -> a
f c -> a
f d -> b
g d -> b
g
inheritStyleHeaderGroup :: (c -> a)
-> (c -> a)
-> (d -> b)
-> (d -> b)
-> TableStyle a b
-> TableStyle c d
c -> a
rowHead c -> a
row d -> b
colHead d -> b
col TableStyle a b
ts =
TableStyle a b
ts { headerSepC = \d
a d
b -> TableStyle a b -> b -> b -> String
forall rowSep colSep.
TableStyle rowSep colSep -> colSep -> colSep -> String
headerSepC TableStyle a b
ts (d -> b
colHead d
a) (d -> b
col d
b)
, headerTopC = headerTopC ts . colHead
, headerC = headerC ts . colHead
, rowHeaderSepC = \c
a c
b -> TableStyle a b -> a -> a -> String
forall rowSep colSep.
TableStyle rowSep colSep -> rowSep -> rowSep -> String
rowHeaderSepC TableStyle a b
ts (c -> a
rowHead c
a) (c -> a
rowHead c
b)
, rowHeaderLeftC = rowHeaderLeftC ts . rowHead
, rowHeaderC = rowHeaderC ts . rowHead
, groupC = groupC ts . col
, groupSepH = groupSepH ts . row
, groupSepC = \c
a d
b -> TableStyle a b -> a -> b -> String
forall rowSep colSep.
TableStyle rowSep colSep -> rowSep -> colSep -> String
groupSepC TableStyle a b
ts (c -> a
row c
a) (d -> b
col d
b)
, groupSepLC = groupSepLC ts . row
, groupSepRC = groupSepRC ts . row
, groupTopC = groupTopC ts . col
, groupBottomC = groupBottomC ts . col
}
withoutBorders :: TableStyle a b -> TableStyle a b
withoutBorders :: forall a b. TableStyle a b -> TableStyle a b
withoutBorders = TableStyle a b -> TableStyle a b
forall a b. TableStyle a b -> TableStyle a b
withoutTopBorder (TableStyle a b -> TableStyle a b)
-> (TableStyle a b -> TableStyle a b)
-> TableStyle a b
-> TableStyle a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableStyle a b -> TableStyle a b
forall a b. TableStyle a b -> TableStyle a b
withoutBottomBorder (TableStyle a b -> TableStyle a b)
-> (TableStyle a b -> TableStyle a b)
-> TableStyle a b
-> TableStyle a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableStyle a b -> TableStyle a b
forall a b. TableStyle a b -> TableStyle a b
withoutLeftBorder (TableStyle a b -> TableStyle a b)
-> (TableStyle a b -> TableStyle a b)
-> TableStyle a b
-> TableStyle a b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableStyle a b -> TableStyle a b
forall a b. TableStyle a b -> TableStyle a b
withoutRightBorder
withoutTopBorder :: TableStyle a b -> TableStyle a b
withoutTopBorder :: forall a b. TableStyle a b -> TableStyle a b
withoutTopBorder TableStyle a b
ts = TableStyle a b
ts { headerTopH = "", headerTopL = "", headerTopR = "", headerTopC = const ""
, rowHeaderLeftT = "", rowHeaderT = "", rowHeaderSepTC = ""
, bothHeadersTL = "", bothHeadersTR = "", bothHeadersT = ""
, groupTopC = const "", groupTopL = "", groupTopR = "", groupTopH = ""
}
withoutBottomBorder :: TableStyle a b -> TableStyle a b
withoutBottomBorder :: forall a b. TableStyle a b -> TableStyle a b
withoutBottomBorder TableStyle a b
ts = TableStyle a b
ts { rowHeaderLeftB = "", rowHeaderB = "", rowHeaderSepBC = ""
, groupBottomC = const "", groupBottomL = "", groupBottomR = "", groupBottomH = "" }
withoutLeftBorder :: TableStyle a b -> TableStyle a b
withoutLeftBorder :: forall a b. TableStyle a b -> TableStyle a b
withoutLeftBorder TableStyle a b
ts = TableStyle a b
ts { headerSepLC = "", headerTopL = "", headerL = ""
, rowHeaderLeftV = "", rowHeaderLeftT = "", rowHeaderLeftB = "", rowHeaderLeftC = const ""
, bothHeadersTL = "", bothHeadersBL = "", bothHeadersL = ""
, groupL = "", groupSepLC = const "", groupTopL = "", groupBottomL = ""
}
withoutRightBorder :: TableStyle a b -> TableStyle a b
withoutRightBorder :: forall a b. TableStyle a b -> TableStyle a b
withoutRightBorder TableStyle a b
ts = TableStyle a b
ts { headerSepRC = "", headerTopR = "", headerR = ""
, groupR = "", groupSepRC = const "", groupTopR = "", groupBottomR = ""
}
withRoundCorners :: TableStyle a b -> TableStyle a b
withRoundCorners :: forall a b. TableStyle a b -> TableStyle a b
withRoundCorners TableStyle a b
ts = TableStyle a b
ts { headerTopL = "╭"
, rowHeaderLeftT = "╭"
, bothHeadersTL = "╭"
, groupTopL = "╭"
, headerTopR = "╮"
, groupTopR = "╮"
, rowHeaderLeftB = "╰"
, groupBottomL = "╰"
, groupBottomR = "╯"
}
data TableStyleSpec
= TableStyleSpec
{ :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, :: LineStyle
, TableStyleSpec -> LineStyle
groupLeft :: LineStyle
, TableStyleSpec -> LineStyle
groupRight :: LineStyle
, TableStyleSpec -> LineStyle
groupTop :: LineStyle
, TableStyleSpec -> LineStyle
groupBottom :: LineStyle
}
simpleTableStyleSpec :: LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec :: LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
headerStyle LineStyle
groupStyle
= TableStyleSpec
{ headerSep :: LineStyle
headerSep = LineStyle
headerStyle
, headerTop :: LineStyle
headerTop = LineStyle
headerStyle
, headerLeft :: LineStyle
headerLeft = LineStyle
headerStyle
, headerRight :: LineStyle
headerRight = LineStyle
headerStyle
, rowHeaderSep :: LineStyle
rowHeaderSep = LineStyle
headerStyle
, rowHeaderLeft :: LineStyle
rowHeaderLeft = LineStyle
headerStyle
, rowHeaderTop :: LineStyle
rowHeaderTop = LineStyle
headerStyle
, rowHeaderBottom :: LineStyle
rowHeaderBottom = LineStyle
headerStyle
, bothHeadersTop :: LineStyle
bothHeadersTop = LineStyle
headerStyle
, bothHeadersBottom :: LineStyle
bothHeadersBottom = LineStyle
headerStyle
, bothHeadersLeft :: LineStyle
bothHeadersLeft = LineStyle
headerStyle
, bothHeadersRight :: LineStyle
bothHeadersRight = LineStyle
headerStyle
, groupLeft :: LineStyle
groupLeft = LineStyle
groupStyle
, groupRight :: LineStyle
groupRight = LineStyle
groupStyle
, groupTop :: LineStyle
groupTop = LineStyle
groupStyle
, groupBottom :: LineStyle
groupBottom = LineStyle
groupStyle
}
asciiTableStyleFromSpec :: TableStyleSpec -> TableStyle LineStyle LineStyle
asciiTableStyleFromSpec :: TableStyleSpec -> TableStyle LineStyle LineStyle
asciiTableStyleFromSpec = (LineStyle -> String)
-> (LineStyle -> String)
-> (LineStyle -> LineStyle -> LineStyle -> LineStyle -> String)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
tableStyleFromSpec LineStyle -> String
asciiHorizontal LineStyle -> String
asciiVertical LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
asciiJoinString4
roundedAsciiTableStyleFromSpec :: TableStyleSpec -> TableStyle LineStyle LineStyle
roundedAsciiTableStyleFromSpec :: TableStyleSpec -> TableStyle LineStyle LineStyle
roundedAsciiTableStyleFromSpec = (LineStyle -> String)
-> (LineStyle -> String)
-> (LineStyle -> LineStyle -> LineStyle -> LineStyle -> String)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
tableStyleFromSpec LineStyle -> String
asciiHorizontal LineStyle -> String
asciiVertical LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
roundedAsciiJoinString4
unicodeTableStyleFromSpec :: TableStyleSpec -> TableStyle LineStyle LineStyle
unicodeTableStyleFromSpec :: TableStyleSpec -> TableStyle LineStyle LineStyle
unicodeTableStyleFromSpec = (LineStyle -> String)
-> (LineStyle -> String)
-> (LineStyle -> LineStyle -> LineStyle -> LineStyle -> String)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
tableStyleFromSpec LineStyle -> String
unicodeHorizontal LineStyle -> String
unicodeVertical LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
unicodeJoinString4
tableStyleFromSpec :: (LineStyle -> String) -> (LineStyle -> String)
-> (LineStyle -> LineStyle -> LineStyle -> LineStyle -> String)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
tableStyleFromSpec :: (LineStyle -> String)
-> (LineStyle -> String)
-> (LineStyle -> LineStyle -> LineStyle -> LineStyle -> String)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
tableStyleFromSpec LineStyle -> String
hString LineStyle -> String
vString LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString TableStyleSpec { LineStyle
headerSep :: TableStyleSpec -> LineStyle
headerTop :: TableStyleSpec -> LineStyle
headerLeft :: TableStyleSpec -> LineStyle
headerRight :: TableStyleSpec -> LineStyle
rowHeaderSep :: TableStyleSpec -> LineStyle
rowHeaderLeft :: TableStyleSpec -> LineStyle
rowHeaderTop :: TableStyleSpec -> LineStyle
rowHeaderBottom :: TableStyleSpec -> LineStyle
bothHeadersTop :: TableStyleSpec -> LineStyle
bothHeadersBottom :: TableStyleSpec -> LineStyle
bothHeadersLeft :: TableStyleSpec -> LineStyle
bothHeadersRight :: TableStyleSpec -> LineStyle
groupLeft :: TableStyleSpec -> LineStyle
groupRight :: TableStyleSpec -> LineStyle
groupTop :: TableStyleSpec -> LineStyle
groupBottom :: TableStyleSpec -> LineStyle
headerSep :: LineStyle
headerTop :: LineStyle
headerLeft :: LineStyle
headerRight :: LineStyle
rowHeaderSep :: LineStyle
rowHeaderLeft :: LineStyle
rowHeaderTop :: LineStyle
rowHeaderBottom :: LineStyle
bothHeadersTop :: LineStyle
bothHeadersBottom :: LineStyle
bothHeadersLeft :: LineStyle
bothHeadersRight :: LineStyle
groupLeft :: LineStyle
groupRight :: LineStyle
groupTop :: LineStyle
groupBottom :: LineStyle
.. }
= TableStyle
{ headerSepH :: String
headerSepH = LineStyle -> String
hString LineStyle
headerSep
, headerSepLC :: String
headerSepLC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
headerSep LineStyle
headerLeft LineStyle
groupLeft
, headerSepRC :: String
headerSepRC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
headerSep LineStyle
NoLine LineStyle
headerRight LineStyle
groupRight
, headerSepC :: LineStyle -> LineStyle -> String
headerSepC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
headerSep LineStyle
headerSep
, headerTopH :: String
headerTopH = LineStyle -> String
hString LineStyle
headerTop
, headerTopL :: String
headerTopL = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
headerTop LineStyle
NoLine LineStyle
headerLeft
, headerTopR :: String
headerTopR = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
headerTop LineStyle
NoLine LineStyle
NoLine LineStyle
headerRight
, headerTopC :: LineStyle -> String
headerTopC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
headerTop LineStyle
headerTop LineStyle
NoLine
, headerL :: String
headerL = LineStyle -> String
vString LineStyle
headerLeft
, headerR :: String
headerR = LineStyle -> String
vString LineStyle
headerRight
, headerC :: LineStyle -> String
headerC = LineStyle -> String
vString
, rowHeaderSepV :: String
rowHeaderSepV = LineStyle -> String
vString LineStyle
rowHeaderSep
, rowHeaderSepTC :: String
rowHeaderSepTC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
rowHeaderTop LineStyle
groupTop LineStyle
NoLine LineStyle
rowHeaderSep
, rowHeaderSepBC :: String
rowHeaderSepBC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
rowHeaderBottom LineStyle
groupBottom LineStyle
rowHeaderSep LineStyle
NoLine
, rowHeaderSepC :: LineStyle -> LineStyle -> String
rowHeaderSepC = \LineStyle
h LineStyle
g -> LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
h LineStyle
g LineStyle
rowHeaderSep LineStyle
rowHeaderSep
, rowHeaderLeftV :: String
rowHeaderLeftV = LineStyle -> String
vString LineStyle
rowHeaderLeft
, rowHeaderLeftT :: String
rowHeaderLeftT = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
rowHeaderTop LineStyle
NoLine LineStyle
rowHeaderLeft
, rowHeaderLeftB :: String
rowHeaderLeftB = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
rowHeaderBottom LineStyle
rowHeaderLeft LineStyle
NoLine
, rowHeaderLeftC :: LineStyle -> String
rowHeaderLeftC = \LineStyle
h -> LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
h LineStyle
rowHeaderLeft LineStyle
rowHeaderLeft
, rowHeaderT :: String
rowHeaderT = LineStyle -> String
hString LineStyle
rowHeaderTop
, rowHeaderB :: String
rowHeaderB = LineStyle -> String
hString LineStyle
rowHeaderBottom
, rowHeaderC :: LineStyle -> String
rowHeaderC = LineStyle -> String
hString
, bothHeadersTL :: String
bothHeadersTL = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
bothHeadersTop LineStyle
NoLine LineStyle
bothHeadersLeft
, bothHeadersTR :: String
bothHeadersTR = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
bothHeadersTop LineStyle
headerTop LineStyle
NoLine LineStyle
bothHeadersRight
, bothHeadersBL :: String
bothHeadersBL = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
bothHeadersBottom LineStyle
bothHeadersLeft LineStyle
rowHeaderLeft
, bothHeadersBR :: String
bothHeadersBR = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
bothHeadersBottom LineStyle
headerSep LineStyle
bothHeadersRight LineStyle
rowHeaderSep
, bothHeadersL :: String
bothHeadersL = LineStyle -> String
vString LineStyle
bothHeadersLeft
, bothHeadersR :: String
bothHeadersR = LineStyle -> String
vString LineStyle
bothHeadersRight
, bothHeadersT :: String
bothHeadersT = LineStyle -> String
hString LineStyle
bothHeadersTop
, bothHeadersB :: String
bothHeadersB = LineStyle -> String
hString LineStyle
bothHeadersBottom
, groupL :: String
groupL = LineStyle -> String
vString LineStyle
groupLeft
, groupR :: String
groupR = LineStyle -> String
vString LineStyle
groupRight
, groupC :: LineStyle -> String
groupC = LineStyle -> String
vString
, groupSepH :: LineStyle -> String
groupSepH = LineStyle -> String
hString
, groupSepC :: LineStyle -> LineStyle -> String
groupSepC = \LineStyle
h LineStyle
v -> LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
h LineStyle
h LineStyle
v LineStyle
v
, groupSepLC :: LineStyle -> String
groupSepLC = \LineStyle
h -> LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
h LineStyle
groupLeft LineStyle
groupLeft
, groupSepRC :: LineStyle -> String
groupSepRC = \LineStyle
h -> LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
h LineStyle
NoLine LineStyle
groupRight LineStyle
groupRight
, groupTopC :: LineStyle -> String
groupTopC = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
groupTop LineStyle
groupTop LineStyle
NoLine
, groupTopL :: String
groupTopL = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
groupTop LineStyle
NoLine LineStyle
groupLeft
, groupTopR :: String
groupTopR = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
groupTop LineStyle
NoLine LineStyle
NoLine LineStyle
groupRight
, groupTopH :: String
groupTopH = LineStyle -> String
hString LineStyle
groupTop
, groupBottomC :: LineStyle -> String
groupBottomC = \LineStyle
v -> LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
groupBottom LineStyle
groupBottom LineStyle
v LineStyle
NoLine
, groupBottomL :: String
groupBottomL = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
NoLine LineStyle
groupBottom LineStyle
groupLeft LineStyle
NoLine
, groupBottomR :: String
groupBottomR = LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
joinString LineStyle
groupBottom LineStyle
NoLine LineStyle
groupRight LineStyle
NoLine
, groupBottomH :: String
groupBottomH = LineStyle -> String
hString LineStyle
groupBottom
}
setTableStyleSpecSeparator :: LineStyle -> TableStyleSpec -> TableStyleSpec
setTableStyleSpecSeparator :: LineStyle -> TableStyleSpec -> TableStyleSpec
setTableStyleSpecSeparator LineStyle
sep TableStyleSpec
spec =
TableStyleSpec
spec { headerSep = sep, rowHeaderSep = sep, bothHeadersBottom = sep, bothHeadersRight = sep }
asciiRoundS :: TableStyle LineStyle LineStyle
asciiRoundS :: TableStyle LineStyle LineStyle
asciiRoundS = (LineStyle -> String)
-> (LineStyle -> String)
-> (LineStyle -> LineStyle -> LineStyle -> LineStyle -> String)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
tableStyleFromSpec LineStyle -> String
asciiHorizontal LineStyle -> String
asciiVertical LineStyle -> LineStyle -> LineStyle -> LineStyle -> String
roundedAsciiJoinString4 (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$
LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
SingleLine LineStyle
SingleLine
asciiS :: TableStyle LineStyle LineStyle
asciiS :: TableStyle LineStyle LineStyle
asciiS = TableStyleSpec -> TableStyle LineStyle LineStyle
asciiTableStyleFromSpec (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$ LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
SingleLine LineStyle
SingleLine
asciiDoubleS :: TableStyle LineStyle LineStyle
asciiDoubleS :: TableStyle LineStyle LineStyle
asciiDoubleS = TableStyleSpec -> TableStyle LineStyle LineStyle
asciiTableStyleFromSpec (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$ LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
DoubleLine LineStyle
SingleLine
unicodeS :: TableStyle LineStyle LineStyle
unicodeS :: TableStyle LineStyle LineStyle
unicodeS = TableStyleSpec -> TableStyle LineStyle LineStyle
unicodeTableStyleFromSpec (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> (TableStyleSpec -> TableStyleSpec)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LineStyle -> TableStyleSpec -> TableStyleSpec
setTableStyleSpecSeparator LineStyle
DoubleLine (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$
LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
SingleLine LineStyle
SingleLine
unicodeBoldHeaderS :: TableStyle LineStyle LineStyle
= (LineStyle -> LineStyle)
-> (LineStyle -> LineStyle)
-> (LineStyle -> LineStyle)
-> (LineStyle -> LineStyle)
-> TableStyle LineStyle LineStyle
-> TableStyle LineStyle LineStyle
forall c a d b.
(c -> a)
-> (c -> a)
-> (d -> b)
-> (d -> b)
-> TableStyle a b
-> TableStyle c d
inheritStyleHeaderGroup LineStyle -> LineStyle
makeLineBold LineStyle -> LineStyle
forall a. a -> a
id LineStyle -> LineStyle
makeLineBold LineStyle -> LineStyle
forall a. a -> a
id (TableStyle LineStyle LineStyle -> TableStyle LineStyle LineStyle)
-> (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec
-> TableStyle LineStyle LineStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
TableStyleSpec -> TableStyle LineStyle LineStyle
unicodeTableStyleFromSpec (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$ LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
HeavyLine LineStyle
SingleLine
unicodeRoundS :: TableStyle LineStyle LineStyle
unicodeRoundS :: TableStyle LineStyle LineStyle
unicodeRoundS = TableStyle LineStyle LineStyle -> TableStyle LineStyle LineStyle
forall a b. TableStyle a b -> TableStyle a b
withRoundCorners TableStyle LineStyle LineStyle
unicodeS
unicodeBoldS :: TableStyle LineStyle LineStyle
unicodeBoldS :: TableStyle LineStyle LineStyle
unicodeBoldS = TableStyleSpec -> TableStyle LineStyle LineStyle
unicodeTableStyleFromSpec (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$ LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
HeavyLine LineStyle
HeavyLine
unicodeBoldStripedS :: TableStyle LineStyle LineStyle
unicodeBoldStripedS :: TableStyle LineStyle LineStyle
unicodeBoldStripedS = TableStyle LineStyle LineStyle
unicodeBoldS
{ groupSepLC = const $ unicodeVertical HeavyLine
, groupSepRC = const $ unicodeVertical HeavyLine
, groupSepC = const unicodeVertical
}
unicodeDoubleFrameS :: TableStyle LineStyle LineStyle
unicodeDoubleFrameS :: TableStyle LineStyle LineStyle
unicodeDoubleFrameS = TableStyleSpec -> TableStyle LineStyle LineStyle
unicodeTableStyleFromSpec (TableStyleSpec -> TableStyle LineStyle LineStyle)
-> TableStyleSpec -> TableStyle LineStyle LineStyle
forall a b. (a -> b) -> a -> b
$ LineStyle -> LineStyle -> TableStyleSpec
simpleTableStyleSpec LineStyle
DoubleLine LineStyle
DoubleLine