{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Graphics.Blank.JavaScript where
import Data.Bits (shiftR, (.&.))
import Data.Char (isAscii, isControl, ord)
import Data.Colour
import Data.Colour.SRGB
import Data.Default.Class
import Data.Ix
import Data.List hiding (length)
import Data.String
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as B (singleton)
import Data.Vector.Unboxed (Vector, toList)
import qualified Data.Vector.Unboxed as V
import Data.Word (Word8)
import Graphics.Blank.Parser
import Prelude.Compat
import Text.ParserCombinators.ReadP (choice, skipSpaces)
import Text.ParserCombinators.ReadPrec (lift)
import Text.Read (Read (..), parens,
readListPrecDefault)
import Numeric (showHex)
import TextShow
import TextShow.Data.Floating (showbFFloat)
import TextShow.Data.Integral (showbHex)
import TextShow.TH (deriveTextShow)
data CanvasContext = CanvasContext Int Int Int deriving (Eq, Ord, Show)
$(deriveTextShow ''CanvasContext)
data CanvasImage = CanvasImage Int Int Int deriving (Eq, Ord, Show)
$(deriveTextShow ''CanvasImage)
newtype CanvasGradient = CanvasGradient Int deriving (Eq, Ord, Show)
$(deriveTextShow ''CanvasGradient)
newtype CanvasPattern = CanvasPattern Int deriving (Eq, Ord, Show)
$(deriveTextShow ''CanvasPattern)
data CanvasAudio = CanvasAudio !Int !Double deriving (Eq, Ord, Show)
$(deriveTextShow ''CanvasAudio)
data ImageData = ImageData !Int !Int !(Vector Word8) deriving (Eq, Ord, Show)
instance TextShow ImageData where
showbPrec p (ImageData w h d) = showbParen (p > 10) $
"ImageData " <> showbPrec 11 w <> showbSpace
<> showbPrec 11 h <> showbSpace
<> showbUnaryWith showbPrec "fromList" 11 (toList d)
class Image a where
jsImage :: a -> Builder
width :: Num b => a -> b
height :: Num b => a -> b
instance Image CanvasImage where
jsImage = jsCanvasImage
width (CanvasImage _ w _) = fromIntegral w
height (CanvasImage _ _ h) = fromIntegral h
instance Image CanvasContext where
jsImage = (<> ".canvas") . jsCanvasContext
width (CanvasContext _ w _) = fromIntegral w
height (CanvasContext _ _ h) = fromIntegral h
class Audio a where
jsAudio :: a -> Builder
duration :: Fractional b => a -> b
instance Audio CanvasAudio where
jsAudio = jsCanvasAudio
duration (CanvasAudio _ d) = realToFrac d
class Style a where
jsStyle :: a -> Builder
instance Style Text where { jsStyle = jsText }
instance Style CanvasGradient where { jsStyle = jsCanvasGradient }
instance Style CanvasPattern where { jsStyle = jsCanvasPattern }
instance Style (Colour Double) where { jsStyle = jsColour }
instance Style (AlphaColour Double) where { jsStyle = jsAlphaColour }
class Style a => CanvasColor a
jsCanvasColor :: CanvasColor color => color -> Builder
jsCanvasColor = jsStyle
instance CanvasColor Text
instance CanvasColor (Colour Double)
instance CanvasColor (AlphaColour Double)
data RepeatDirection = Repeat
| RepeatX
| RepeatY
| NoRepeat
deriving (Bounded, Enum, Eq, Ix, Ord)
repeat_ :: RepeatDirection
repeat_ = Repeat
repeatX :: RepeatDirection
repeatX = RepeatX
repeatY :: RepeatDirection
repeatY = RepeatY
noRepeat :: RepeatDirection
noRepeat = NoRepeat
instance Default RepeatDirection where
def = Repeat
instance IsString RepeatDirection where
fromString = read
instance Read RepeatDirection where
readPrec = parens . lift $ do
skipSpaces
choice
[ Repeat <$ stringCI "repeat"
, RepeatX <$ stringCI "repeat-x"
, RepeatY <$ stringCI "repeat-y"
, NoRepeat <$ stringCI "no-repeat"
]
readListPrec = readListPrecDefault
instance Show RepeatDirection where
showsPrec p = showsPrec p . FromTextShow
instance TextShow RepeatDirection where
showb Repeat = "repeat"
showb RepeatX = "repeat-x"
showb RepeatY = "repeat-y"
showb NoRepeat = "no-repeat"
data LineEndCap = ButtCap
| RoundCap
| SquareCap
deriving (Bounded, Enum, Eq, Ix, Ord)
butt :: LineEndCap
butt = ButtCap
square :: LineEndCap
square = SquareCap
instance Default LineEndCap where
def = ButtCap
instance IsString LineEndCap where
fromString = read
instance Read LineEndCap where
readPrec = parens . lift $ do
skipSpaces
choice
[ ButtCap <$ stringCI "butt"
, RoundCap <$ stringCI "round"
, SquareCap <$ stringCI "square"
]
readListPrec = readListPrecDefault
instance RoundProperty LineEndCap where
round_ = RoundCap
instance Show LineEndCap where
showsPrec p = showsPrec p . FromTextShow
instance TextShow LineEndCap where
showb ButtCap = "butt"
showb RoundCap = "round"
showb SquareCap = "square"
data LineJoinCorner = BevelCorner
| RoundCorner
| MiterCorner
deriving (Bounded, Enum, Eq, Ix, Ord)
bevel :: LineJoinCorner
bevel = BevelCorner
miter :: LineJoinCorner
miter = MiterCorner
instance Default LineJoinCorner where
def = MiterCorner
instance IsString LineJoinCorner where
fromString = read
instance Read LineJoinCorner where
readPrec = parens . lift $ do
skipSpaces
choice
[ BevelCorner <$ stringCI "bevel"
, RoundCorner <$ stringCI "round"
, MiterCorner <$ stringCI "miter"
]
readListPrec = readListPrecDefault
instance RoundProperty LineJoinCorner where
round_ = RoundCorner
instance Show LineJoinCorner where
showsPrec p = showsPrec p . FromTextShow
instance TextShow LineJoinCorner where
showb BevelCorner = "bevel"
showb RoundCorner = "round"
showb MiterCorner = "miter"
data TextAnchorAlignment = StartAnchor
| EndAnchor
| CenterAnchor
| LeftAnchor
| RightAnchor
deriving (Bounded, Enum, Eq, Ix, Ord)
start :: TextAnchorAlignment
start = StartAnchor
end :: TextAnchorAlignment
end = EndAnchor
center :: TextAnchorAlignment
center = CenterAnchor
left :: TextAnchorAlignment
left = LeftAnchor
right :: TextAnchorAlignment
right = RightAnchor
instance Default TextAnchorAlignment where
def = StartAnchor
instance IsString TextAnchorAlignment where
fromString = read
instance Read TextAnchorAlignment where
readPrec = parens . lift $ do
skipSpaces
choice
[ StartAnchor <$ stringCI "start"
, EndAnchor <$ stringCI "end"
, CenterAnchor <$ stringCI "center"
, LeftAnchor <$ stringCI "left"
, RightAnchor <$ stringCI "right"
]
readListPrec = readListPrecDefault
instance Show TextAnchorAlignment where
showsPrec p = showsPrec p . FromTextShow
instance TextShow TextAnchorAlignment where
showb StartAnchor = "start"
showb EndAnchor = "end"
showb CenterAnchor = "center"
showb LeftAnchor = "left"
showb RightAnchor = "right"
data TextBaselineAlignment = TopBaseline
| HangingBaseline
| MiddleBaseline
| AlphabeticBaseline
| IdeographicBaseline
| BottomBaseline
deriving (Bounded, Enum, Eq, Ix, Ord)
top :: TextBaselineAlignment
top = TopBaseline
hanging :: TextBaselineAlignment
hanging = HangingBaseline
middle :: TextBaselineAlignment
middle = MiddleBaseline
alphabetic :: TextBaselineAlignment
alphabetic = AlphabeticBaseline
ideographic :: TextBaselineAlignment
ideographic = IdeographicBaseline
bottom :: TextBaselineAlignment
bottom = BottomBaseline
instance Default TextBaselineAlignment where
def = AlphabeticBaseline
instance IsString TextBaselineAlignment where
fromString = read
instance Read TextBaselineAlignment where
readPrec = parens . lift $ do
skipSpaces
choice
[ TopBaseline <$ stringCI "top"
, HangingBaseline <$ stringCI "hanging"
, MiddleBaseline <$ stringCI "middle"
, AlphabeticBaseline <$ stringCI "alphabetic"
, IdeographicBaseline <$ stringCI "ideographic"
, BottomBaseline <$ stringCI "bottom"
]
readListPrec = readListPrecDefault
instance Show TextBaselineAlignment where
showsPrec p = showsPrec p . FromTextShow
instance TextShow TextBaselineAlignment where
showb TopBaseline = "top"
showb HangingBaseline = "hanging"
showb MiddleBaseline = "middle"
showb AlphabeticBaseline = "alphabetic"
showb IdeographicBaseline = "ideographic"
showb BottomBaseline = "bottom"
class RoundProperty a where
round_ :: a
class JSArg a where
showbJS :: a -> Builder
instance JSArg (AlphaColour Double) where
showbJS = jsAlphaColour
jsAlphaColour :: AlphaColour Double -> Builder
jsAlphaColour aCol
| a >= 1 = jsColour rgbCol
| a <= 0 = jsLiteralBuilder "rgba(0,0,0,0)"
| otherwise = jsLiteralBuilder $ "rgba("
<> showb r <> B.singleton ','
<> showb g <> B.singleton ','
<> showb b <> B.singleton ','
<> jsDouble a <> B.singleton ')'
where
a = alphaChannel aCol
rgbCol = darken (recip a) $ aCol `over` black
RGB r g b = toSRGB24 rgbCol
instance JSArg Bool where
showbJS = jsBool
jsBool :: Bool -> Builder
jsBool True = "true"
jsBool False = "false"
instance JSArg CanvasAudio where
showbJS = jsCanvasAudio
jsCanvasAudio :: CanvasAudio -> Builder
jsCanvasAudio (CanvasAudio n _ ) = "sounds[" <> showb n <> B.singleton ']'
instance JSArg CanvasContext where
showbJS = jsCanvasContext
jsCanvasContext :: CanvasContext -> Builder
jsCanvasContext (CanvasContext n _ _) = "canvasbuffers[" <> showb n <> B.singleton ']'
instance JSArg CanvasImage where
showbJS = jsCanvasImage
jsCanvasImage :: CanvasImage -> Builder
jsCanvasImage (CanvasImage n _ _) = "images[" <> showb n <> B.singleton ']'
instance JSArg CanvasGradient where
showbJS = jsCanvasGradient
jsCanvasGradient :: CanvasGradient -> Builder
jsCanvasGradient (CanvasGradient n) = "gradient_" <> showb n
instance JSArg CanvasPattern where
showbJS = jsCanvasPattern
jsCanvasPattern :: CanvasPattern -> Builder
jsCanvasPattern (CanvasPattern n) = "pattern_" <> showb n
instance JSArg (Colour Double) where
showbJS = jsColour
jsColour :: Colour Double -> Builder
jsColour = jsLiteralBuilder . sRGB24showb
sRGB24showb :: (Floating b, RealFrac b) => Colour b -> Builder
sRGB24showb c =
B.singleton '#' <> showbHex2 r' <> showbHex2 g' <> showbHex2 b'
where
RGB r' g' b' = toSRGB24 c
showbHex2 x | x <= 0xf = B.singleton '0' <> showbHex x
| otherwise = showbHex x
instance JSArg Double where
showbJS = jsDouble
jsDouble :: Double -> Builder
jsDouble = showbFFloat $ Just 3
instance JSArg ImageData where
showbJS = jsImageData
jsImageData :: ImageData -> Builder
jsImageData (ImageData w h d) = "ImageData(" <> showb w
<> B.singleton ',' <> showb h
<> ",[" <> vs <> "])"
where
vs = jsList showb $ V.toList d
instance JSArg Int where
showbJS = jsInt
jsInt :: Int -> Builder
jsInt = showb
instance JSArg LineEndCap where
showbJS = jsLineEndCap
jsLineEndCap :: LineEndCap -> Builder
jsLineEndCap = jsLiteralBuilder . showb
instance JSArg LineJoinCorner where
showbJS = jsLineJoinCorner
jsLineJoinCorner :: LineJoinCorner -> Builder
jsLineJoinCorner = jsLiteralBuilder . showb
jsList :: (a -> Builder) -> [a] -> Builder
jsList js = mconcat . intersperse "," . map js
instance JSArg RepeatDirection where
showbJS = jsRepeatDirection
jsRepeatDirection :: RepeatDirection -> Builder
jsRepeatDirection = jsLiteralBuilder . showb
instance JSArg Text where
showbJS = jsText
jsText :: Text -> Builder
jsText = jsLiteralBuilder . fromText
instance JSArg TextAnchorAlignment where
showbJS = jsTextAnchorAlignment
jsTextAnchorAlignment :: TextAnchorAlignment -> Builder
jsTextAnchorAlignment = jsLiteralBuilder . showb
instance JSArg TextBaselineAlignment where
showbJS = jsTextBaselineAlignment
jsTextBaselineAlignment :: TextBaselineAlignment -> Builder
jsTextBaselineAlignment = jsLiteralBuilder . showb
jsLiteralBuilder :: Builder -> Builder
jsLiteralBuilder = jsQuoteBuilder . jsEscapeBuilder
jsQuoteBuilder :: Builder -> Builder
jsQuoteBuilder b = B.singleton '"' <> b <> B.singleton '"'
jsEscapeBuilder :: Builder -> Builder
jsEscapeBuilder = fromLazyText . TL.concatMap jsEscapeChar . toLazyText
jsEscapeChar :: Char -> TL.Text
jsEscapeChar '\\' = "\\\\"
jsEscapeChar '\b' = "\\b"
jsEscapeChar '\f' = "\\f"
jsEscapeChar '\n' = "\\n"
jsEscapeChar '\r' = "\\r"
jsEscapeChar '\t' = "\\t"
jsEscapeChar '\v' = "\\v"
jsEscapeChar '\"' = "\\\""
jsEscapeChar '\'' = "\\'"
jsEscapeChar '/' = "\\/"
jsEscapeChar c
| not (isControl c) && isAscii c = TL.singleton c
| ord c <= 0xff = hexxs "\\x" 2 (ord c)
| ord c <= 0xffff = hexxs "\\u" 4 (ord c)
| otherwise = let cp0 = ord c - 0x10000
in hexxs "\\u" 4 ((cp0 `shiftR` 10) + 0xd800) `mappend`
hexxs "\\u" 4 ((cp0 .&. 0x3ff) + 0xdc00)
where hexxs prefix pad cp =
let h = showHex cp ""
in TL.pack (prefix ++ replicate (pad - length h) '0' ++ h)