{-# LANGUAGE OverloadedStrings #-}
module Graphics.Layout.CSS.Internal where
import Data.CSS.Syntax.Tokens (Token(..), NumericValue(..))
import qualified Data.Text as Txt
import Data.Scientific (toRealFloat)
import Debug.Trace (trace) -- For warnings.
import Graphics.Layout.Box hiding (lowerLength)
type Unitted = (Double, Txt.Text)
auto :: Unitted
auto = (0,"auto")
parseLength :: [Token] -> Maybe Unitted
parseLength [Percentage _ x] = Just (n2f x,"%")
parseLength [Dimension _ x unit]
| n2f x == 0 && unit == "" = Just (0,"px")
| unit `elem` units = Just (n2f x,unit)
parseLength [Ident "auto"] = Just (0,"auto")
parseLength [Ident "initial"] = Just (0,"auto")
parseLength _ = Nothing
parseLength' [Ident "min-content"] = Just (0,"min-content")
parseLength' [Ident "max-content"] = Just (0,"max-content")
parseLength' toks = parseLength toks
units = Txt.words "cap ch em ex ic lh rem rlh vh vw vmax vmin vb vi px cm mm Q in pc pt %"
n2f (NVInteger x) = realToFrac x
n2f (NVNumber x) = toRealFloat x
lowerLength :: Unitted -> Font' -> Length
lowerLength (x,"cap") f = Pixels $ x*fontHeight f 'A'
lowerLength (x,"ch") f = Pixels $ x*fontAdvance f '0'
lowerLength (x,"em") f = Pixels $ x*fontSize f
lowerLength (x,"ex") f = Pixels $ x*fontHeight f 'x'
lowerLength (x,"ic") f = Pixels $ x*fontHeight f '水' -- CJK water ideograph
lowerLength (x,"lh") f = Pixels $ x*lineheight f -- Store conversion factors in `f`...
lowerLength (x,"rem") f = Pixels $ x*rootEm f
lowerLength (x,"rlh") f = Pixels $ x*rlh f
lowerLength (x,"vh") f = Pixels $ x*vh f
lowerLength (x,"vw") f = Pixels $ x*vw f
lowerLength (x,"vmax") f = Percent $ x*vmax f
lowerLength (x,"vmin") f = Percent $ x*vmin f
lowerLength (x,"vb") f = Percent $ x*vb f -- This'll be trickier to populate
lowerLength (x,"vi") f = Percent $ x*vi f -- This'll be trickier to populate
lowerLength (x,"px") f = Pixels $ x*scale f
lowerLength (x,"cm") f = Pixels $ x*scale f*96/2.54
lowerLength (x,"mm") f | Pixels x' <- lowerLength (x,"cm") f = Pixels $ x'/10
lowerLength (x,"Q") f | Pixels x' <- lowerLength (x,"cm") f = Pixels $ x'/40
lowerLength (x,"pc") f | Pixels x' <- lowerLength (x,"in") f = Pixels $ x'/6
lowerLength (x,"pt") f | Pixels x' <- lowerLength (x,"in") f = Pixels $ x'/72
lowerLength (x,"%") _ = Percent $ x/100
lowerLength (_,"auto") _ = Auto
lowerLength (_,unit) _ = trace ("Invalid unit " ++ Txt.unpack unit) $ Pixels 0
data Font' = Font' {
fontHeight :: Char -> Double,
fontAdvance :: Char -> Double,
fontSize :: Double,
rootEm :: Double,
lineheight :: Double,
rlh :: Double,
vh :: Double,
vw :: Double,
vmax :: Double,
vmin :: Double,
vb :: Double,
vi :: Double,
scale :: Double
}