{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -Wno-type-defaults #-}
module Clay.Grid
(
gridGap
, gridTemplateColumns
, GridLine
, ToGridLine
, GridLines2
, ToGridLines2
, GridLines4
, ToGridLines4
, OneGridLine
, TwoGridLines
, ThreeGridLines
, FourGridLines
, CustomIdentGrid
, customIdentToText
, partialMkCustomIdentGrid
, ToSpan
, gridArea
, gridColumn
, gridColumnStart
, gridColumnEnd
, gridRow
, gridRowStart
, gridRowEnd
, (//)
, span_
)
where
import qualified Clay.Common as Com
import Clay.Property (Val, Value, noCommas, value)
import Clay.Size (Size)
import Clay.Stylesheet (Css, key)
import Data.Char (isNumber)
import Data.Text (Text)
import qualified Data.Text as T
import Prelude
gridGap :: Size a -> Css
gridGap :: forall a. Size a -> Css
gridGap = Key (Size a) -> Size a -> Css
forall a. Val a => Key a -> a -> Css
key Key (Size a)
"grid-gap"
gridTemplateColumns :: [Size a] -> Css
gridTemplateColumns :: forall a. [Size a] -> Css
gridTemplateColumns = Key Value -> Value -> Css
forall a. Val a => Key a -> a -> Css
key Key Value
"grid-template-columns" (Value -> Css) -> ([Size a] -> Value) -> [Size a] -> Css
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Size a] -> Value
forall a. Val a => [a] -> Value
noCommas
data GridLine
= Coordinate Integer
| GridLineCustomIdent CustomIdentGrid (Maybe Integer)
| Span (Maybe CustomIdentGrid) (Maybe Integer)
| OtherGridLine Value
deriving (GridLine -> GridLine -> Bool
(GridLine -> GridLine -> Bool)
-> (GridLine -> GridLine -> Bool) -> Eq GridLine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GridLine -> GridLine -> Bool
== :: GridLine -> GridLine -> Bool
$c/= :: GridLine -> GridLine -> Bool
/= :: GridLine -> GridLine -> Bool
Eq, Int -> GridLine -> ShowS
[GridLine] -> ShowS
GridLine -> String
(Int -> GridLine -> ShowS)
-> (GridLine -> String) -> ([GridLine] -> ShowS) -> Show GridLine
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GridLine -> ShowS
showsPrec :: Int -> GridLine -> ShowS
$cshow :: GridLine -> String
show :: GridLine -> String
$cshowList :: [GridLine] -> ShowS
showList :: [GridLine] -> ShowS
Show)
class ToGridLine a where
toGridLine :: a -> GridLine
instance ToGridLine GridLine where
toGridLine :: GridLine -> GridLine
toGridLine = GridLine -> GridLine
forall a. a -> a
id
instance ToGridLine Integer where
toGridLine :: Integer -> GridLine
toGridLine = Integer -> GridLine
Coordinate
instance ToGridLine CustomIdentGrid where
toGridLine :: CustomIdentGrid -> GridLine
toGridLine CustomIdentGrid
x = CustomIdentGrid -> Maybe Integer -> GridLine
GridLineCustomIdent CustomIdentGrid
x Maybe Integer
forall a. Maybe a
Nothing
instance ToGridLine String where
toGridLine :: String -> GridLine
toGridLine = CustomIdentGrid -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine (CustomIdentGrid -> GridLine)
-> (String -> CustomIdentGrid) -> String -> GridLine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CustomIdentGrid
partialMkCustomIdentGrid (Text -> CustomIdentGrid)
-> (String -> Text) -> String -> CustomIdentGrid
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
instance ToGridLine (CustomIdentGrid, Integer) where
toGridLine :: (CustomIdentGrid, Integer) -> GridLine
toGridLine (CustomIdentGrid
x, Integer
y) = CustomIdentGrid -> Maybe Integer -> GridLine
GridLineCustomIdent CustomIdentGrid
x (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
y)
instance ToGridLine (String, Integer) where
toGridLine :: (String, Integer) -> GridLine
toGridLine (String
x, Integer
y) = (CustomIdentGrid, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine (Text -> CustomIdentGrid
partialMkCustomIdentGrid (Text -> CustomIdentGrid) -> Text -> CustomIdentGrid
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
x, Integer
y)
data GridLines2
= One2 OneGridLine
| Two2 TwoGridLines
class ToGridLines2 a where
toGridLines2 :: a -> GridLines2
instance ToGridLines2 GridLine where
toGridLines2 :: GridLine -> GridLines2
toGridLines2 = OneGridLine -> GridLines2
One2 (OneGridLine -> GridLines2)
-> (GridLine -> OneGridLine) -> GridLine -> GridLines2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GridLine -> OneGridLine
OneGridLine
instance ToGridLines2 OneGridLine where
toGridLines2 :: OneGridLine -> GridLines2
toGridLines2 = OneGridLine -> GridLines2
One2
instance ToGridLines2 TwoGridLines where
toGridLines2 :: TwoGridLines -> GridLines2
toGridLines2 = TwoGridLines -> GridLines2
Two2
instance ToGridLines2 GridLines2 where
toGridLines2 :: GridLines2 -> GridLines2
toGridLines2 = GridLines2 -> GridLines2
forall a. a -> a
id
instance ToGridLines2 Integer where
toGridLines2 :: Integer -> GridLines2
toGridLines2 = GridLine -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
toGridLines2 (GridLine -> GridLines2)
-> (Integer -> GridLine) -> Integer -> GridLines2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines2 CustomIdentGrid where
toGridLines2 :: CustomIdentGrid -> GridLines2
toGridLines2 = GridLine -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
toGridLines2 (GridLine -> GridLines2)
-> (CustomIdentGrid -> GridLine) -> CustomIdentGrid -> GridLines2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomIdentGrid -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines2 String where
toGridLines2 :: String -> GridLines2
toGridLines2 = GridLine -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
toGridLines2 (GridLine -> GridLines2)
-> (String -> GridLine) -> String -> GridLines2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines2 (CustomIdentGrid, Integer) where
toGridLines2 :: (CustomIdentGrid, Integer) -> GridLines2
toGridLines2 = GridLine -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
toGridLines2 (GridLine -> GridLines2)
-> ((CustomIdentGrid, Integer) -> GridLine)
-> (CustomIdentGrid, Integer)
-> GridLines2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CustomIdentGrid, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines2 (String, Integer) where
toGridLines2 :: (String, Integer) -> GridLines2
toGridLines2 = GridLine -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
toGridLines2 (GridLine -> GridLines2)
-> ((String, Integer) -> GridLine)
-> (String, Integer)
-> GridLines2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
data GridLines4
= One4 OneGridLine
| Two4 TwoGridLines
| Three4 ThreeGridLines
| Four4 FourGridLines
class ToGridLines4 a where
toGridLines4 :: a -> GridLines4
instance ToGridLines4 GridLine where
toGridLines4 :: GridLine -> GridLines4
toGridLines4 = OneGridLine -> GridLines4
One4 (OneGridLine -> GridLines4)
-> (GridLine -> OneGridLine) -> GridLine -> GridLines4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GridLine -> OneGridLine
OneGridLine
instance ToGridLines4 OneGridLine where
toGridLines4 :: OneGridLine -> GridLines4
toGridLines4 = OneGridLine -> GridLines4
One4
instance ToGridLines4 TwoGridLines where
toGridLines4 :: TwoGridLines -> GridLines4
toGridLines4 = TwoGridLines -> GridLines4
Two4
instance ToGridLines4 ThreeGridLines where
toGridLines4 :: ThreeGridLines -> GridLines4
toGridLines4 = ThreeGridLines -> GridLines4
Three4
instance ToGridLines4 FourGridLines where
toGridLines4 :: FourGridLines -> GridLines4
toGridLines4 = FourGridLines -> GridLines4
Four4
instance ToGridLines4 GridLines4 where
toGridLines4 :: GridLines4 -> GridLines4
toGridLines4 = GridLines4 -> GridLines4
forall a. a -> a
id
instance ToGridLines4 Integer where
toGridLines4 :: Integer -> GridLines4
toGridLines4 = GridLine -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
toGridLines4 (GridLine -> GridLines4)
-> (Integer -> GridLine) -> Integer -> GridLines4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines4 CustomIdentGrid where
toGridLines4 :: CustomIdentGrid -> GridLines4
toGridLines4 = GridLine -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
toGridLines4 (GridLine -> GridLines4)
-> (CustomIdentGrid -> GridLine) -> CustomIdentGrid -> GridLines4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomIdentGrid -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines4 String where
toGridLines4 :: String -> GridLines4
toGridLines4 = GridLine -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
toGridLines4 (GridLine -> GridLines4)
-> (String -> GridLine) -> String -> GridLines4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines4 (CustomIdentGrid, Integer) where
toGridLines4 :: (CustomIdentGrid, Integer) -> GridLines4
toGridLines4 = GridLine -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
toGridLines4 (GridLine -> GridLines4)
-> ((CustomIdentGrid, Integer) -> GridLine)
-> (CustomIdentGrid, Integer)
-> GridLines4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CustomIdentGrid, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
instance ToGridLines4 (String, Integer) where
toGridLines4 :: (String, Integer) -> GridLines4
toGridLines4 = GridLine -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
toGridLines4 (GridLine -> GridLines4)
-> ((String, Integer) -> GridLine)
-> (String, Integer)
-> GridLines4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
newtype OneGridLine = OneGridLine GridLine
data TwoGridLines = TwoGridLines GridLine GridLine
data ThreeGridLines = ThreeGridLines GridLine GridLine GridLine
data FourGridLines = FourGridLines GridLine GridLine GridLine GridLine
newtype CustomIdentGrid = CustomIdentGrid Text deriving (CustomIdentGrid -> CustomIdentGrid -> Bool
(CustomIdentGrid -> CustomIdentGrid -> Bool)
-> (CustomIdentGrid -> CustomIdentGrid -> Bool)
-> Eq CustomIdentGrid
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CustomIdentGrid -> CustomIdentGrid -> Bool
== :: CustomIdentGrid -> CustomIdentGrid -> Bool
$c/= :: CustomIdentGrid -> CustomIdentGrid -> Bool
/= :: CustomIdentGrid -> CustomIdentGrid -> Bool
Eq, Eq CustomIdentGrid
Eq CustomIdentGrid =>
(CustomIdentGrid -> CustomIdentGrid -> Ordering)
-> (CustomIdentGrid -> CustomIdentGrid -> Bool)
-> (CustomIdentGrid -> CustomIdentGrid -> Bool)
-> (CustomIdentGrid -> CustomIdentGrid -> Bool)
-> (CustomIdentGrid -> CustomIdentGrid -> Bool)
-> (CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid)
-> (CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid)
-> Ord CustomIdentGrid
CustomIdentGrid -> CustomIdentGrid -> Bool
CustomIdentGrid -> CustomIdentGrid -> Ordering
CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid
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 :: CustomIdentGrid -> CustomIdentGrid -> Ordering
compare :: CustomIdentGrid -> CustomIdentGrid -> Ordering
$c< :: CustomIdentGrid -> CustomIdentGrid -> Bool
< :: CustomIdentGrid -> CustomIdentGrid -> Bool
$c<= :: CustomIdentGrid -> CustomIdentGrid -> Bool
<= :: CustomIdentGrid -> CustomIdentGrid -> Bool
$c> :: CustomIdentGrid -> CustomIdentGrid -> Bool
> :: CustomIdentGrid -> CustomIdentGrid -> Bool
$c>= :: CustomIdentGrid -> CustomIdentGrid -> Bool
>= :: CustomIdentGrid -> CustomIdentGrid -> Bool
$cmax :: CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid
max :: CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid
$cmin :: CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid
min :: CustomIdentGrid -> CustomIdentGrid -> CustomIdentGrid
Ord, ReadPrec [CustomIdentGrid]
ReadPrec CustomIdentGrid
Int -> ReadS CustomIdentGrid
ReadS [CustomIdentGrid]
(Int -> ReadS CustomIdentGrid)
-> ReadS [CustomIdentGrid]
-> ReadPrec CustomIdentGrid
-> ReadPrec [CustomIdentGrid]
-> Read CustomIdentGrid
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CustomIdentGrid
readsPrec :: Int -> ReadS CustomIdentGrid
$creadList :: ReadS [CustomIdentGrid]
readList :: ReadS [CustomIdentGrid]
$creadPrec :: ReadPrec CustomIdentGrid
readPrec :: ReadPrec CustomIdentGrid
$creadListPrec :: ReadPrec [CustomIdentGrid]
readListPrec :: ReadPrec [CustomIdentGrid]
Read, Int -> CustomIdentGrid -> ShowS
[CustomIdentGrid] -> ShowS
CustomIdentGrid -> String
(Int -> CustomIdentGrid -> ShowS)
-> (CustomIdentGrid -> String)
-> ([CustomIdentGrid] -> ShowS)
-> Show CustomIdentGrid
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CustomIdentGrid -> ShowS
showsPrec :: Int -> CustomIdentGrid -> ShowS
$cshow :: CustomIdentGrid -> String
show :: CustomIdentGrid -> String
$cshowList :: [CustomIdentGrid] -> ShowS
showList :: [CustomIdentGrid] -> ShowS
Show)
customIdentToText :: CustomIdentGrid -> Text
customIdentToText :: CustomIdentGrid -> Text
customIdentToText (CustomIdentGrid Text
x) = Text
x
partialMkCustomIdentGrid :: Text -> CustomIdentGrid
partialMkCustomIdentGrid :: Text -> CustomIdentGrid
partialMkCustomIdentGrid Text
"span" = String -> CustomIdentGrid
forall a. HasCallStack => String -> a
error String
"Custom-ident for a grid property cannot be named span"
partialMkCustomIdentGrid Text
txt = CustomIdentGrid
checkText
where
checkText :: CustomIdentGrid
checkText = Char -> CustomIdentGrid
checkHead ((Char, Text) -> Char
forall a b. (a, b) -> a
fst (Char, Text)
unconsTxt)
checkHead :: Char -> CustomIdentGrid
checkHead :: Char -> CustomIdentGrid
checkHead Char
c
| Char -> Bool
isNumber Char
c = String -> CustomIdentGrid
forall a. HasCallStack => String -> a
error String
"Custom-ident cannot start with a number"
| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' = Maybe Char -> CustomIdentGrid
checkSecond Maybe Char
second
| Bool
otherwise = Text -> CustomIdentGrid
CustomIdentGrid Text
txt
checkSecond :: Maybe Char -> CustomIdentGrid
checkSecond (Just Char
s)
| Char
s Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' =
String -> CustomIdentGrid
forall a. HasCallStack => String -> a
error String
"Custom-ident cannot start with two hyphens"
| Char -> Bool
isNumber Char
s =
String -> CustomIdentGrid
forall a. HasCallStack => String -> a
error String
"Custom-ident cannot start with a hyphen followed by a number"
| Bool
otherwise = Text -> CustomIdentGrid
CustomIdentGrid Text
txt
checkSecond Maybe Char
Nothing = Text -> CustomIdentGrid
CustomIdentGrid Text
txt
unconsTxt :: (Char, Text)
unconsTxt = case Text -> Maybe (Char, Text)
T.uncons Text
txt of
Maybe (Char, Text)
Nothing -> String -> (Char, Text)
forall a. HasCallStack => String -> a
error String
"Custom-ident cannot be empty"
Just (Char
f, Text
r) -> (Char
f, Text
r)
second :: Maybe Char
second :: Maybe Char
second = (Char, Text) -> Char
forall a b. (a, b) -> a
fst ((Char, Text) -> Char) -> Maybe (Char, Text) -> Maybe Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe (Char, Text)
T.uncons ((Char, Text) -> Text
forall a b. (a, b) -> b
snd (Char, Text)
unconsTxt)
gridArea :: ToGridLines4 a => a -> Css
gridArea :: forall a. ToGridLines4 a => a -> Css
gridArea a
x = Key GridLines4 -> GridLines4 -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLines4
"grid-area" (a -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
partialToGridLines4 a
x)
gridColumn :: ToGridLines2 a => a -> Css
gridColumn :: forall a. ToGridLines2 a => a -> Css
gridColumn a
x = Key GridLines2 -> GridLines2 -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLines2
"grid-column" (a -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
partialToGridLines2 a
x)
gridColumnStart :: ToGridLine a => a -> Css
gridColumnStart :: forall a. ToGridLine a => a -> Css
gridColumnStart a
x = Key GridLine -> GridLine -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLine
"grid-column-start" (a -> GridLine
forall a. ToGridLine a => a -> GridLine
partialToGridLine a
x)
gridColumnEnd :: ToGridLine a => a -> Css
gridColumnEnd :: forall a. ToGridLine a => a -> Css
gridColumnEnd a
x = Key GridLine -> GridLine -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLine
"grid-column-end" (a -> GridLine
forall a. ToGridLine a => a -> GridLine
partialToGridLine a
x)
gridRow :: ToGridLines2 a => a -> Css
gridRow :: forall a. ToGridLines2 a => a -> Css
gridRow a
x = Key GridLines2 -> GridLines2 -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLines2
"grid-row" (a -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
partialToGridLines2 a
x)
gridRowStart :: ToGridLine a => a -> Css
gridRowStart :: forall a. ToGridLine a => a -> Css
gridRowStart a
x = Key GridLine -> GridLine -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLine
"grid-row-start" (a -> GridLine
forall a. ToGridLine a => a -> GridLine
partialToGridLine a
x)
gridRowEnd :: ToGridLine a => a -> Css
gridRowEnd :: forall a. ToGridLine a => a -> Css
gridRowEnd a
x = Key GridLine -> GridLine -> Css
forall a. Val a => Key a -> a -> Css
key Key GridLine
"grid-row-end" (a -> GridLine
forall a. ToGridLine a => a -> GridLine
partialToGridLine a
x)
class Slash a r | a -> r where
(//) :: ToGridLine b => a -> b -> r
instance Slash GridLine TwoGridLines where
GridLine
x // :: forall b. ToGridLine b => GridLine -> b -> TwoGridLines
// b
y = GridLine -> GridLine -> TwoGridLines
TwoGridLines GridLine
x (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash Integer TwoGridLines where
Integer
x // :: forall b. ToGridLine b => Integer -> b -> TwoGridLines
// b
y = GridLine -> GridLine -> TwoGridLines
TwoGridLines (Integer -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine Integer
x) (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash CustomIdentGrid TwoGridLines where
CustomIdentGrid
x // :: forall b. ToGridLine b => CustomIdentGrid -> b -> TwoGridLines
// b
y = GridLine -> GridLine -> TwoGridLines
TwoGridLines (CustomIdentGrid -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine CustomIdentGrid
x) (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash String TwoGridLines where
String
x // :: forall b. ToGridLine b => String -> b -> TwoGridLines
// b
y = GridLine -> GridLine -> TwoGridLines
TwoGridLines (String -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine String
x) (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash (CustomIdentGrid, Integer) TwoGridLines where
(CustomIdentGrid, Integer)
x // :: forall b.
ToGridLine b =>
(CustomIdentGrid, Integer) -> b -> TwoGridLines
// b
y = GridLine -> GridLine -> TwoGridLines
TwoGridLines ((CustomIdentGrid, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine (CustomIdentGrid, Integer)
x) (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash (String, Integer) TwoGridLines where
(String, Integer)
x // :: forall b. ToGridLine b => (String, Integer) -> b -> TwoGridLines
// b
y = GridLine -> GridLine -> TwoGridLines
TwoGridLines ((String, Integer) -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine (String, Integer)
x) (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash TwoGridLines ThreeGridLines where
(TwoGridLines GridLine
xx GridLine
xy) // :: forall b. ToGridLine b => TwoGridLines -> b -> ThreeGridLines
// b
y = GridLine -> GridLine -> GridLine -> ThreeGridLines
ThreeGridLines GridLine
xx GridLine
xy (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
instance Slash ThreeGridLines FourGridLines where
(ThreeGridLines GridLine
xx GridLine
xy GridLine
xz) // :: forall b. ToGridLine b => ThreeGridLines -> b -> FourGridLines
// b
y = GridLine -> GridLine -> GridLine -> GridLine -> FourGridLines
FourGridLines GridLine
xx GridLine
xy GridLine
xz (b -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine b
y)
class ToSpan a where
span_ :: a -> GridLine
instance ToSpan Integer where
span_ :: Integer -> GridLine
span_ Integer
x = Maybe CustomIdentGrid -> Maybe Integer -> GridLine
Span Maybe CustomIdentGrid
forall a. Maybe a
Nothing (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
x)
instance ToSpan String where
span_ :: String -> GridLine
span_ String
x = Maybe CustomIdentGrid -> Maybe Integer -> GridLine
Span (CustomIdentGrid -> Maybe CustomIdentGrid
forall a. a -> Maybe a
Just (CustomIdentGrid -> Maybe CustomIdentGrid)
-> (Text -> CustomIdentGrid) -> Text -> Maybe CustomIdentGrid
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CustomIdentGrid
partialMkCustomIdentGrid (Text -> Maybe CustomIdentGrid) -> Text -> Maybe CustomIdentGrid
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
x) Maybe Integer
forall a. Maybe a
Nothing
instance ToSpan (String, Integer) where
span_ :: (String, Integer) -> GridLine
span_ (String
x, Integer
y) = Maybe CustomIdentGrid -> Maybe Integer -> GridLine
Span (CustomIdentGrid -> Maybe CustomIdentGrid
forall a. a -> Maybe a
Just (CustomIdentGrid -> Maybe CustomIdentGrid)
-> (Text -> CustomIdentGrid) -> Text -> Maybe CustomIdentGrid
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CustomIdentGrid
partialMkCustomIdentGrid (Text -> Maybe CustomIdentGrid) -> Text -> Maybe CustomIdentGrid
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
x) (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
y)
instance Com.Auto GridLine where
auto :: GridLine
auto = Value -> GridLine
OtherGridLine (Value -> GridLine) -> Value -> GridLine
forall a b. (a -> b) -> a -> b
$ Text -> Value
forall a. Val a => a -> Value
value (Text
"auto" :: Text)
instance Com.Inherit GridLine where
inherit :: GridLine
inherit = Value -> GridLine
OtherGridLine (Value -> GridLine) -> Value -> GridLine
forall a b. (a -> b) -> a -> b
$ Text -> Value
forall a. Val a => a -> Value
value (Text
"inherit" :: Text)
instance Com.Initial GridLine where
initial :: GridLine
initial = Value -> GridLine
OtherGridLine (Value -> GridLine) -> Value -> GridLine
forall a b. (a -> b) -> a -> b
$ Text -> Value
forall a. Val a => a -> Value
value (Text
"initial" :: Text)
instance Com.Unset GridLine where
unset :: GridLine
unset = Value -> GridLine
OtherGridLine (Value -> GridLine) -> Value -> GridLine
forall a b. (a -> b) -> a -> b
$ Text -> Value
forall a. Val a => a -> Value
value (Text
"unset" :: Text)
instance Val GridLine where
value :: GridLine -> Value
value (OtherGridLine Value
val) = Value
val
value (Coordinate Integer
x) = Integer -> Value
forall a. Val a => a -> Value
value Integer
x
value (GridLineCustomIdent CustomIdentGrid
x Maybe Integer
y) =
Text -> Value
forall a. Val a => a -> Value
value (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ CustomIdentGrid -> Text
customIdentToText CustomIdentGrid
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Integer -> Text) -> Maybe Integer -> Text
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Integer -> Text) -> Integer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Text
forall a. Show a => a -> Text
tshow) Maybe Integer
y
value (Span Maybe CustomIdentGrid
x Maybe Integer
y) =
Text -> Value
forall a. Val a => a -> Value
value (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"span" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (CustomIdentGrid -> Text) -> Maybe CustomIdentGrid -> Text
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)
(Text -> Text)
-> (CustomIdentGrid -> Text) -> CustomIdentGrid -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CustomIdentGrid -> Text
customIdentToText) Maybe CustomIdentGrid
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Integer -> Text) -> Maybe Integer -> Text
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Integer -> Text) -> Integer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Text
forall a. Show a => a -> Text
tshow) Maybe Integer
y
instance Val OneGridLine where
value :: OneGridLine -> Value
value (OneGridLine GridLine
x) = GridLine -> Value
forall a. Val a => a -> Value
value GridLine
x
instance Val TwoGridLines where
value :: TwoGridLines -> Value
value (TwoGridLines GridLine
x GridLine
y) =
GridLine -> Value
forall a. Val a => a -> Value
value GridLine
x Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value (Text
" / " :: Text) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> GridLine -> Value
forall a. Val a => a -> Value
value GridLine
y
instance Val ThreeGridLines where
value :: ThreeGridLines -> Value
value (ThreeGridLines GridLine
x GridLine
y GridLine
z) =
GridLine -> Value
forall a. Val a => a -> Value
value GridLine
x
Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value (Text
" / " :: Text) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> GridLine -> Value
forall a. Val a => a -> Value
value GridLine
y
Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value (Text
" / " :: Text) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> GridLine -> Value
forall a. Val a => a -> Value
value GridLine
z
instance Val FourGridLines where
value :: FourGridLines -> Value
value (FourGridLines GridLine
xx GridLine
xy GridLine
xz GridLine
yx) =
GridLine -> Value
forall a. Val a => a -> Value
value GridLine
xx
Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value (Text
" / " :: Text) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> GridLine -> Value
forall a. Val a => a -> Value
value GridLine
xy
Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value (Text
" / " :: Text) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> GridLine -> Value
forall a. Val a => a -> Value
value GridLine
xz
Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> Text -> Value
forall a. Val a => a -> Value
value (Text
" / " :: Text) Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
<> GridLine -> Value
forall a. Val a => a -> Value
value GridLine
yx
instance Val GridLines2 where
value :: GridLines2 -> Value
value (One2 OneGridLine
x) = OneGridLine -> Value
forall a. Val a => a -> Value
value OneGridLine
x
value (Two2 TwoGridLines
x) = TwoGridLines -> Value
forall a. Val a => a -> Value
value TwoGridLines
x
instance Val GridLines4 where
value :: GridLines4 -> Value
value (One4 OneGridLine
x) = OneGridLine -> Value
forall a. Val a => a -> Value
value OneGridLine
x
value (Two4 TwoGridLines
x) = TwoGridLines -> Value
forall a. Val a => a -> Value
value TwoGridLines
x
value (Three4 ThreeGridLines
x) = ThreeGridLines -> Value
forall a. Val a => a -> Value
value ThreeGridLines
x
value (Four4 FourGridLines
x) = FourGridLines -> Value
forall a. Val a => a -> Value
value FourGridLines
x
partialCheckGridLine :: GridLine -> GridLine
partialCheckGridLine :: GridLine -> GridLine
partialCheckGridLine GridLine
gridLine = case GridLine
gridLine of
Coordinate Integer
0 -> Integer -> GridLine
forall {a} {a}. Show a => a -> a
errorValue Integer
0
GridLineCustomIdent CustomIdentGrid
_ (Just Integer
0) -> Integer -> GridLine
forall {a} {a}. Show a => a -> a
errorValue Integer
0
s :: GridLine
s@(Span Maybe CustomIdentGrid
_ (Just Integer
n)) -> if Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
1
then Integer -> GridLine
forall {a} {a}. Show a => a -> a
errorValue Integer
n
else GridLine
s
GridLine
_ -> GridLine
gridLine
where
errorValue :: a -> a
errorValue a
n = String -> a
forall a. HasCallStack => String -> a
error (String
"Value " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is invalid")
partialCheckOneGridLine :: OneGridLine -> OneGridLine
partialCheckOneGridLine :: OneGridLine -> OneGridLine
partialCheckOneGridLine (OneGridLine GridLine
gridLine) =
GridLine -> OneGridLine
OneGridLine (GridLine -> GridLine
partialCheckGridLine GridLine
gridLine)
partialCheckTwoGridLines :: TwoGridLines -> TwoGridLines
partialCheckTwoGridLines :: TwoGridLines -> TwoGridLines
partialCheckTwoGridLines (TwoGridLines GridLine
gridLine1 GridLine
gridLine2) =
GridLine -> GridLine -> TwoGridLines
TwoGridLines (GridLine -> GridLine
partialCheckGridLine GridLine
gridLine1) (GridLine -> GridLine
partialCheckGridLine GridLine
gridLine2)
partialCheckThreeGridLines :: ThreeGridLines -> ThreeGridLines
partialCheckThreeGridLines :: ThreeGridLines -> ThreeGridLines
partialCheckThreeGridLines (ThreeGridLines GridLine
gridLine1 GridLine
gridLine2 GridLine
gridLine3) =
GridLine -> GridLine -> GridLine -> ThreeGridLines
ThreeGridLines
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine1)
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine2)
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine3)
partialCheckFourGridLines :: FourGridLines -> FourGridLines
partialCheckFourGridLines :: FourGridLines -> FourGridLines
partialCheckFourGridLines
(FourGridLines GridLine
gridLine1 GridLine
gridLine2 GridLine
gridLine3 GridLine
gridLine4) =
GridLine -> GridLine -> GridLine -> GridLine -> FourGridLines
FourGridLines
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine1)
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine2)
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine3)
(GridLine -> GridLine
partialCheckGridLine GridLine
gridLine4)
partialToGridLine :: ToGridLine a => a -> GridLine
partialToGridLine :: forall a. ToGridLine a => a -> GridLine
partialToGridLine = GridLine -> GridLine
partialCheckGridLine (GridLine -> GridLine) -> (a -> GridLine) -> a -> GridLine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> GridLine
forall a. ToGridLine a => a -> GridLine
toGridLine
partialToGridLines2 :: ToGridLines2 a => a -> GridLines2
partialToGridLines2 :: forall a. ToGridLines2 a => a -> GridLines2
partialToGridLines2 a
x = GridLines2 -> GridLines2
partialGridLine' GridLines2
gridLines
where
gridLines :: GridLines2
gridLines = a -> GridLines2
forall a. ToGridLines2 a => a -> GridLines2
toGridLines2 a
x
partialGridLine' :: GridLines2 -> GridLines2
partialGridLine' (One2 OneGridLine
gl) = OneGridLine -> GridLines2
One2 (OneGridLine -> OneGridLine
partialCheckOneGridLine OneGridLine
gl)
partialGridLine' (Two2 TwoGridLines
gl) = TwoGridLines -> GridLines2
Two2 (TwoGridLines -> TwoGridLines
partialCheckTwoGridLines TwoGridLines
gl)
partialToGridLines4 :: ToGridLines4 a => a -> GridLines4
partialToGridLines4 :: forall a. ToGridLines4 a => a -> GridLines4
partialToGridLines4 a
x = GridLines4 -> GridLines4
partialGridLine' GridLines4
gridLines
where
gridLines :: GridLines4
gridLines = a -> GridLines4
forall a. ToGridLines4 a => a -> GridLines4
toGridLines4 a
x
partialGridLine' :: GridLines4 -> GridLines4
partialGridLine' (One4 OneGridLine
gl) = OneGridLine -> GridLines4
One4 (OneGridLine -> OneGridLine
partialCheckOneGridLine OneGridLine
gl)
partialGridLine' (Two4 TwoGridLines
gl) = TwoGridLines -> GridLines4
Two4 (TwoGridLines -> TwoGridLines
partialCheckTwoGridLines TwoGridLines
gl)
partialGridLine' (Three4 ThreeGridLines
gl) = ThreeGridLines -> GridLines4
Three4 (ThreeGridLines -> ThreeGridLines
partialCheckThreeGridLines ThreeGridLines
gl)
partialGridLine' (Four4 FourGridLines
gl) = FourGridLines -> GridLines4
Four4 (FourGridLines -> FourGridLines
partialCheckFourGridLines FourGridLines
gl)
tshow :: Show a => a -> Text
tshow :: forall a. Show a => a -> Text
tshow = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show