module Graphics.Blank.Types.Font where
import Control.Applicative
import Control.Monad
import Data.Char
import Data.Default.Class
import Data.Ix (Ix)
import Data.Maybe
import Data.Monoid
import Data.String
import qualified Data.Text as TS
import Data.Text (Text)
import qualified Data.Text.Lazy.Builder as B (singleton)
import Graphics.Blank.JavaScript
import Graphics.Blank.Parser
import Graphics.Blank.Types
import Graphics.Blank.Types.CSS
import qualified Text.ParserCombinators.ReadP as ReadP
import Text.ParserCombinators.ReadP hiding ((<++), choice, pfail)
import qualified Text.ParserCombinators.ReadPrec as ReadPrec
import Text.ParserCombinators.ReadPrec (ReadPrec, (<++), lift, pfail)
import Text.Read (Read(..), readListPrecDefault)
import TextShow (TextShow(..), Builder, FromTextShow(..), showbSpace)
class CanvasFont a where
jsCanvasFont :: a -> Builder
instance CanvasFont Text where
jsCanvasFont = jsText
instance CanvasFont Font where
jsCanvasFont = jsFont
data Font = FontProperties
{ fontStyle :: FontStyle
, fontVariant :: FontVariant
, fontWeight :: FontWeight
, fontSize :: FontSize
, lineHeight :: LineHeight
, fontFamily :: [FontFamily]
}
| CaptionFont
| IconFont
| MenuFont
| MessageBoxFont
| SmallCaptionFont
| StatusBarFont
deriving (Eq, Ord)
defFont :: [FontFamily] -> Font
defFont = FontProperties def def def def def
caption :: Font
caption = CaptionFont
icon :: Font
icon = IconFont
menu :: Font
menu = MenuFont
messageBox :: Font
messageBox = MessageBoxFont
smallCaption :: Font
smallCaption = SmallCaptionFont
statusBar :: Font
statusBar = StatusBarFont
instance IsString Font where
fromString = read
instance JSArg Font where
showbJS = jsFont
jsFont :: Font -> Builder
jsFont = jsLiteralBuilder . showb
instance Read Font where
readPrec = do
lift skipSpaces
ReadPrec.choice
[ CaptionFont <$ lift (stringCI "caption")
, IconFont <$ lift (stringCI "icon")
, MenuFont <$ lift (stringCI "menu")
, MessageBoxFont <$ lift (stringCI "message-box")
, SmallCaptionFont <$ lift (stringCI "small-caption")
, StatusBarFont <$ lift (stringCI "status-bar")
, readFontProperties Nothing Nothing Nothing
]
readListPrec = readListPrecDefault
data OneOfThree a b c = One a | Two b | Three c
readFontProperties :: Maybe FontStyle -> Maybe FontVariant -> Maybe FontWeight -> ReadPrec Font
readFontProperties style variant weight =
if isJust style && isJust variant && isJust weight
then readFontProperties' style variant weight
else do
let parseCheck :: Maybe a -> ReadPrec a -> ReadPrec a
parseCheck mb parser = if isJust mb then pfail else parser
readStyle, readVariant, readWeight :: ReadPrec (OneOfThree FontStyle FontVariant FontWeight)
readStyle = One <$> parseCheck style readPrec
readVariant = Two <$> parseCheck variant readPrec
readWeight = Three <$> parseCheck weight readPrec
prop <- maybeReadPrec $ readStyle <++ readVariant <++ readWeight
case prop of
Just (One style') -> do
when (isJust style) pfail
readFontProperties (Just style') variant weight
Just (Two variant') -> do
when (isJust variant) pfail
readFontProperties style (Just variant') weight
Just (Three weight') -> do
when (isJust weight) pfail
readFontProperties style variant (Just weight')
Nothing -> readFontProperties' style variant weight
readFontProperties' :: Maybe FontStyle -> Maybe FontVariant -> Maybe FontWeight -> ReadPrec Font
readFontProperties' mbStyle mbVariant mbWeight =
FontProperties (fromMaybe def mbStyle) (fromMaybe def mbVariant) (fromMaybe def mbWeight)
<$> readPrec
<*> lift (option def $ skipSpaces *> char '/' *> unlift readPrec)
<*> (lift (munch1 isSpace) *> readPrec)
instance Show Font where
showsPrec p = showsPrec p . FromTextShow
instance TextShow Font where
showb (FontProperties style variant weight size height' family)
= showb style
<> showbSpace
<> showb variant
<> showbSpace
<> showb weight
<> showbSpace
<> showb size
<> B.singleton '/'
<> showb height'
<> showbSpace
<> showb family
showb CaptionFont = "caption"
showb IconFont = "icon"
showb MenuFont = "menu"
showb MessageBoxFont = "message-box"
showb SmallCaptionFont = "small-caption"
showb StatusBarFont = "status-bar"
data FontStyle = NormalStyle
| ItalicStyle
| ObliqueStyle
deriving (Bounded, Enum, Eq, Ix, Ord)
italic :: FontStyle
italic = ItalicStyle
oblique :: FontStyle
oblique = ObliqueStyle
instance Default FontStyle where
def = NormalStyle
instance IsString FontStyle where
fromString = read
instance NormalProperty FontStyle
instance Read FontStyle where
readPrec = lift $ do
skipSpaces
ReadP.choice
[ NormalStyle <$ stringCI "normal"
, ItalicStyle <$ stringCI "italic"
, ObliqueStyle <$ stringCI "oblique"
]
readListPrec = readListPrecDefault
instance Show FontStyle where
showsPrec p = showsPrec p . FromTextShow
instance TextShow FontStyle where
showb NormalStyle = "normal"
showb ItalicStyle = "italic"
showb ObliqueStyle = "oblique"
data FontVariant = NormalVariant
| SmallCapsVariant
deriving (Bounded, Enum, Eq, Ix, Ord)
smallCaps :: FontVariant
smallCaps = SmallCapsVariant
instance Default FontVariant where
def = NormalVariant
instance IsString FontVariant where
fromString = read
instance NormalProperty FontVariant
instance Read FontVariant where
readPrec = lift $ do
skipSpaces
(NormalVariant <$ stringCI "normal") <|> (SmallCapsVariant <$ stringCI "small-caps")
readListPrec = readListPrecDefault
instance Show FontVariant where
showsPrec p = showsPrec p . FromTextShow
instance TextShow FontVariant where
showb NormalVariant = "normal"
showb SmallCapsVariant = "small-caps"
data FontWeight = NormalWeight
| BoldWeight
| BolderWeight
| LighterWeight
| Weight100
| Weight200
| Weight300
| Weight400
| Weight500
| Weight600
| Weight700
| Weight800
| Weight900
deriving (Bounded, Enum, Eq, Ix, Ord)
bold :: FontWeight
bold = BoldWeight
bolder :: FontWeight
bolder = BolderWeight
lighter :: FontWeight
lighter = LighterWeight
fontWeightError :: a
fontWeightError = error "invalid font-weight operation"
instance Default FontWeight where
def = NormalWeight
instance IsString FontWeight where
fromString = read
instance NormalProperty FontWeight
instance Num FontWeight where
(+) = fontWeightError
() = fontWeightError
(*) = fontWeightError
abs = fontWeightError
signum = fontWeightError
fromInteger 100 = Weight100
fromInteger 200 = Weight200
fromInteger 300 = Weight300
fromInteger 400 = Weight400
fromInteger 500 = Weight500
fromInteger 600 = Weight600
fromInteger 700 = Weight700
fromInteger 800 = Weight800
fromInteger 900 = Weight900
fromInteger _ = fontWeightError
instance Read FontWeight where
readPrec = lift $ do
skipSpaces
ReadP.choice
[ NormalWeight <$ stringCI "normal"
, BoldWeight <$ stringCI "bold"
, BolderWeight <$ stringCI "bolder"
, LighterWeight <$ stringCI "lighter"
, Weight100 <$ string "100"
, Weight200 <$ string "200"
, Weight300 <$ string "300"
, Weight400 <$ string "400"
, Weight500 <$ string "500"
, Weight600 <$ string "600"
, Weight700 <$ string "700"
, Weight800 <$ string "800"
, Weight900 <$ string "900"
]
readListPrec = readListPrecDefault
instance Show FontWeight where
showsPrec p = showsPrec p . FromTextShow
instance TextShow FontWeight where
showb NormalWeight = "normal"
showb BoldWeight = "bold"
showb BolderWeight = "bolder"
showb LighterWeight = "lighter"
showb Weight100 = "100"
showb Weight200 = "200"
showb Weight300 = "300"
showb Weight400 = "400"
showb Weight500 = "500"
showb Weight600 = "600"
showb Weight700 = "700"
showb Weight800 = "800"
showb Weight900 = "900"
data FontSize = XXSmallSize
| XSmallSize
| SmallSize
| MediumSize
| LargeSize
| XLargeSize
| XXLargeSize
| LargerSize
| SmallerSize
| FontSizeLength Length
| FontSizePercentage Percentage
deriving (Eq, Ord)
xxSmall :: FontSize
xxSmall = XXSmallSize
xSmall :: FontSize
xSmall = XSmallSize
small :: FontSize
small = SmallSize
medium :: FontSize
medium = MediumSize
large :: FontSize
large = LargeSize
xLarge :: FontSize
xLarge = XLargeSize
xxLarge :: FontSize
xxLarge = XXLargeSize
larger :: FontSize
larger = LargerSize
smaller :: FontSize
smaller = SmallerSize
instance Default FontSize where
def = MediumSize
instance IsString FontSize where
fromString = read
instance LengthProperty FontSize where
fromLength = FontSizeLength
instance PercentageProperty FontSize where
percent = FontSizePercentage
instance Read FontSize where
readPrec = do
lift $ skipSpaces
ReadPrec.choice
[ XXSmallSize <$ lift (stringCI "xx-small")
, XSmallSize <$ lift (stringCI "x-small")
, SmallSize <$ lift (stringCI "small")
, MediumSize <$ lift (stringCI "medium")
, LargeSize <$ lift (stringCI "large")
, XLargeSize <$ lift (stringCI "x-large")
, XXLargeSize <$ lift (stringCI "xx-large")
, LargerSize <$ lift (stringCI "larger")
, SmallerSize <$ lift (stringCI "smaller")
, FontSizeLength <$> readPrec
, FontSizePercentage <$> readPrec <* lift (char '%')
]
readListPrec = readListPrecDefault
instance Show FontSize where
showsPrec p = showsPrec p . FromTextShow
instance TextShow FontSize where
showb XXSmallSize = "xx-small"
showb XSmallSize = "x-small"
showb SmallSize = "small"
showb MediumSize = "medium"
showb LargeSize = "large"
showb XLargeSize = "x-large"
showb XXLargeSize = "xx-large"
showb LargerSize = "larger"
showb SmallerSize = "smaller"
showb (FontSizeLength l) = showb l
showb (FontSizePercentage p) = jsDouble p <> B.singleton '%'
data LineHeight = NormalLineHeight
| LineHeightNumber Double
| LineHeightLength Length
| LineHeightPercentage Percentage
deriving (Eq, Ord)
lineHeightError :: a
lineHeightError = error "no arithmetic for line-height"
instance Default LineHeight where
def = NormalLineHeight
instance Fractional LineHeight where
(/) = lineHeightError
recip = lineHeightError
fromRational = LineHeightNumber . fromRational
instance IsString LineHeight where
fromString = read
instance LengthProperty LineHeight where
fromLength = LineHeightLength
instance NormalProperty LineHeight
instance Num LineHeight where
(+) = lineHeightError
() = lineHeightError
(*) = lineHeightError
abs = lineHeightError
signum = lineHeightError
fromInteger = LineHeightNumber . fromInteger
instance PercentageProperty LineHeight where
percent = LineHeightPercentage
instance Read LineHeight where
readPrec = do
lift skipSpaces
ReadPrec.choice
[ NormalLineHeight <$ lift (stringCI "normal")
, LineHeightNumber <$> readPrec
, LineHeightLength <$> readPrec
, LineHeightPercentage <$> readPrec <* lift (char '%')
]
readListPrec = readListPrecDefault
instance Show LineHeight where
showsPrec p = showsPrec p . FromTextShow
instance TextShow LineHeight where
showb NormalLineHeight = "normal"
showb (LineHeightNumber n) = jsDouble n
showb (LineHeightLength l) = showb l
showb (LineHeightPercentage p) = jsDouble p <> B.singleton '%'
data FontFamily = FontFamilyName Text
| SerifFamily
| SansSerifFamily
| MonospaceFamily
| CursiveFamily
| FantasyFamily
deriving (Eq, Ord)
serif :: FontFamily
serif = SerifFamily
sansSerif :: FontFamily
sansSerif = SansSerifFamily
monospace :: FontFamily
monospace = MonospaceFamily
cursive :: FontFamily
cursive = CursiveFamily
fantasy :: FontFamily
fantasy = FantasyFamily
instance IsString FontFamily where
fromString = read
instance IsString [FontFamily] where
fromString = read
instance Read FontFamily where
readPrec = lift $ do
skipSpaces
ReadP.choice
[ SerifFamily <$ stringCI "serif"
, SansSerifFamily <$ stringCI "sans-serif"
, MonospaceFamily <$ stringCI "monospace"
, CursiveFamily <$ stringCI "cursive"
, FantasyFamily <$ stringCI "fantasy"
, let quoted quote = between (char quote) (char quote)
in quoted '"' (readFontFamily $ Just '"')
<|> quoted '\'' (readFontFamily $ Just '\'')
<|> readFontFamily Nothing
]
readListPrec = lift . sepBy1 (unlift readPrec) $ skipSpaces *> char ','
readFontFamily :: Maybe Char -> ReadP FontFamily
readFontFamily mQuote = do
name <- case mQuote of
Just quote -> munch (/= quote)
Nothing -> unwords <$> sepBy1 cssIdent (munch1 isSpace)
return . FontFamilyName $ TS.pack name
instance Show FontFamily where
showsPrec p = showsPrec p . FromTextShow
showList = showsPrec 0 . FromTextShow
instance TextShow FontFamily where
showb (FontFamilyName name) = showb name
showb SerifFamily = "serif"
showb SansSerifFamily = "sans-serif"
showb MonospaceFamily = "monospace"
showb CursiveFamily = "cursive"
showb FantasyFamily = "fantasy"
showbList = jsList showb
class Default a => NormalProperty a where
normal :: a
normal = def