module Graphics.Blank.Types.CSS where
import Data.Monoid ((<>))
import Data.String
import Graphics.Blank.JavaScript
import Graphics.Blank.Parser
import Graphics.Blank.Types
import Prelude.Compat
import Text.ParserCombinators.ReadP (choice)
import Text.ParserCombinators.ReadPrec (lift)
import Text.Read (Read(..), readListPrecDefault)
import TextShow (TextShow(..), FromTextShow(..))
data Length = Em { runLength :: Double }
| Ex { runLength :: Double }
| Ch { runLength :: Double }
| Rem { runLength :: Double }
| Vh { runLength :: Double }
| Vw { runLength :: Double }
| Vmin { runLength :: Double }
| Vmax { runLength :: Double }
| Px { runLength :: Double }
| Mm { runLength :: Double }
| Cm { runLength :: Double }
| In { runLength :: Double }
| Pt { runLength :: Double }
| Pc { runLength :: Double }
deriving (Eq, Ord)
class LengthProperty a where
fromLength :: Length -> a
instance LengthProperty Length where
fromLength = id
em :: LengthProperty a => Double -> a
em = fromLength . Em
ex :: LengthProperty a => Double -> a
ex = fromLength . Ex
ch :: LengthProperty a => Double -> a
ch = fromLength . Ch
rem_ :: LengthProperty a => Double -> a
rem_ = fromLength . Rem
vh :: LengthProperty a => Double -> a
vh = fromLength . Vh
vw :: LengthProperty a => Double -> a
vw = fromLength . Vw
vmin :: LengthProperty a => Double -> a
vmin = fromLength . Vmin
vmax :: LengthProperty a => Double -> a
vmax = fromLength . Vmax
px :: LengthProperty a => Double -> a
px = fromLength . Px
mm :: LengthProperty a => Double -> a
mm = fromLength . Mm
cm :: LengthProperty a => Double -> a
cm = fromLength . Cm
in_ :: LengthProperty a => Double -> a
in_ = fromLength . In
pt :: LengthProperty a => Double -> a
pt = fromLength . Pt
pc :: LengthProperty a => Double -> a
pc = fromLength . Pc
instance IsString Length where
fromString = read
instance Read Length where
readPrec = do
d <- readPrec
lift $ choice
[ Em d <$ stringCI "em"
, Ex d <$ stringCI "ex"
, Ch d <$ stringCI "ch"
, Rem d <$ stringCI "rem"
, Vh d <$ stringCI "vh"
, Vw d <$ stringCI "vw"
, Vmin d <$ stringCI "vmin"
, Vmax d <$ stringCI "vmax"
, Px d <$ stringCI "px"
, Mm d <$ stringCI "mm"
, Cm d <$ stringCI "cm"
, In d <$ stringCI "in"
, Pt d <$ stringCI "pt"
, Pc d <$ stringCI "pc"
]
readListPrec = readListPrecDefault
instance Show Length where
showsPrec p = showsPrec p . FromTextShow
instance TextShow Length where
showb l = jsDouble (runLength l) <> showbUnits l
where
showbUnits (Em _) = "em"
showbUnits (Ex _) = "ex"
showbUnits (Ch _) = "ch"
showbUnits (Rem _) = "rem"
showbUnits (Vh _) = "vh"
showbUnits (Vw _) = "vw"
showbUnits (Vmin _) = "vmin"
showbUnits (Vmax _) = "vmax"
showbUnits (Px _) = "px"
showbUnits (Mm _) = "mm"
showbUnits (Cm _) = "cm"
showbUnits (In _) = "in"
showbUnits (Pt _) = "pt"
showbUnits (Pc _) = "pc"
class PercentageProperty a where
percent :: Percentage -> a
instance PercentageProperty Percentage where
percent = id