module Graphics.Blank.JavaScript where
import Control.Applicative
import Data.Char (isControl, isAscii, ord)
import Data.Colour
import Data.Colour.SRGB
import Data.Default.Class
import Data.Ix
import Data.List
import Data.String
import Data.Text (Text, unpack)
import Data.Word (Word8)
import qualified Data.Vector.Unboxed as V
import Data.Vector.Unboxed (Vector)
import Numeric
import Text.ParserCombinators.ReadP (skipSpaces, string)
import Text.ParserCombinators.ReadPrec
import Text.Read
class Image a where
jsImage :: a -> String
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 Style a where
jsStyle :: a -> String
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 -> String
jsCanvasColor = jsStyle
instance CanvasColor Text
instance CanvasColor (Colour Double)
instance CanvasColor (AlphaColour Double)
data CanvasContext = CanvasContext Int Int Int
deriving (Show,Eq,Ord)
data CanvasImage = CanvasImage Int Int Int deriving (Show,Eq,Ord)
newtype CanvasGradient = CanvasGradient Int deriving (Show,Eq,Ord)
newtype CanvasPattern = CanvasPattern Int deriving (Show,Eq,Ord)
data RepeatDirection = Repeat
| RepeatX
| RepeatY
| NoRepeat
deriving Eq
instance Default RepeatDirection where
def = Repeat
instance IsString RepeatDirection where
fromString = read
instance Read RepeatDirection where
readPrec = parens . lift $ do
skipSpaces
(string "repeat" >> return Repeat)
<|> (string "repeat-x" >> return RepeatX)
<|> (string "repeat-y" >> return RepeatY)
<|> (string "no-repeat" >> return NoRepeat)
instance Show RepeatDirection where
showsPrec _ rd = showString $ case rd of
Repeat -> "repeat"
RepeatX -> "repeat-x"
RepeatY -> "repeat-y"
NoRepeat -> "no-repeat"
data LineEndCap = ButtCap
| RoundCap
| SquareCap
deriving Eq
instance Default LineEndCap where
def = ButtCap
instance IsString LineEndCap where
fromString = read
instance Read LineEndCap where
readPrec = parens $ do
Ident s <- lexP
case s of
"butt" -> return ButtCap
"round" -> return RoundCap
"square" -> return SquareCap
_ -> pfail
instance Show LineEndCap where
showsPrec _ le = showString $ case le of
ButtCap -> "butt"
RoundCap -> "round"
SquareCap -> "square"
data LineJoinCorner = BevelCorner
| RoundCorner
| MiterCorner
deriving Eq
instance Default LineJoinCorner where
def = MiterCorner
instance IsString LineJoinCorner where
fromString = read
instance Read LineJoinCorner where
readPrec = parens $ do
Ident s <- lexP
case s of
"bevel" -> return BevelCorner
"round" -> return RoundCorner
"miter" -> return MiterCorner
_ -> pfail
instance Show LineJoinCorner where
showsPrec _ corner = showString $ case corner of
BevelCorner -> "bevel"
RoundCorner -> "round"
MiterCorner -> "miter"
data TextAnchorAlignment = StartAnchor
| EndAnchor
| CenterAnchor
| LeftAnchor
| RightAnchor
deriving Eq
instance Default TextAnchorAlignment where
def = StartAnchor
instance IsString TextAnchorAlignment where
fromString = read
instance Read TextAnchorAlignment where
readPrec = parens $ do
Ident s <- lexP
case s of
"start" -> return StartAnchor
"end" -> return EndAnchor
"center" -> return CenterAnchor
"left" -> return LeftAnchor
"right" -> return RightAnchor
_ -> pfail
instance Show TextAnchorAlignment where
showsPrec _ align = showString $ case align of
StartAnchor -> "start"
EndAnchor -> "end"
CenterAnchor -> "center"
LeftAnchor -> "left"
RightAnchor -> "right"
data TextBaselineAlignment = TopBaseline
| HangingBaseline
| MiddleBaseline
| AlphabeticBaseline
| IdeographicBaseline
| BottomBaseline
deriving (Bounded, Eq, Ix, Ord)
instance Default TextBaselineAlignment where
def = AlphabeticBaseline
instance IsString TextBaselineAlignment where
fromString = read
instance Read TextBaselineAlignment where
readPrec = parens $ do
Ident s <- lexP
case s of
"top" -> return TopBaseline
"hanging" -> return HangingBaseline
"middle" -> return MiddleBaseline
"alphabetic" -> return AlphabeticBaseline
"ideographic" -> return IdeographicBaseline
"bottom" -> return BottomBaseline
_ -> pfail
instance Show TextBaselineAlignment where
showsPrec _ bl = showString $ case bl of
TopBaseline -> "top"
HangingBaseline -> "hanging"
MiddleBaseline -> "middle"
AlphabeticBaseline -> "alphabetic"
IdeographicBaseline -> "ideographic"
BottomBaseline -> "bottom"
data ImageData = ImageData !Int !Int !(Vector Word8) deriving (Show, Eq, Ord)
class JSArg a where
showJS :: a -> String
instance JSArg (AlphaColour Double) where
showJS aCol
| a >= 1 = jsColour rgbCol
| a <= 0 = jsLiteralString "rgba(0,0,0,0)"
| otherwise = jsLiteralString $ "rgba("
++ show r ++ ","
++ show g ++ ","
++ show b ++ ","
++ jsDouble a ++ ")"
where
a = alphaChannel aCol
rgbCol = darken (recip a) $ aCol `over` black
RGB r g b = toSRGB24 rgbCol
jsAlphaColour :: AlphaColour Double -> String
jsAlphaColour = showJS
instance JSArg Bool where
showJS True = "true"
showJS False = "false"
jsBool :: Bool -> String
jsBool = showJS
instance JSArg CanvasContext where
showJS (CanvasContext n _ _) = "canvasbuffers[" ++ show n ++ "]"
jsCanvasContext :: CanvasContext -> String
jsCanvasContext = showJS
instance JSArg CanvasImage where
showJS (CanvasImage n _ _) = "images[" ++ show n ++ "]"
jsCanvasImage :: CanvasImage -> String
jsCanvasImage = showJS
instance JSArg CanvasGradient where
showJS (CanvasGradient n) = "gradients[" ++ show n ++ "]"
jsCanvasGradient :: CanvasGradient -> String
jsCanvasGradient = showJS
instance JSArg CanvasPattern where
showJS (CanvasPattern n) = "patterns[" ++ show n ++ "]"
jsCanvasPattern :: CanvasPattern -> String
jsCanvasPattern = showJS
instance JSArg (Colour Double) where
showJS = jsLiteralString . sRGB24show
jsColour :: Colour Double -> String
jsColour = showJS
instance JSArg Double where
showJS a = showFFloat (Just 3) a ""
jsDouble :: Double -> String
jsDouble = showJS
instance JSArg ImageData where
showJS (ImageData w h d) = "ImageData(" ++ show w ++ "," ++ show h ++ ",[" ++ vs ++ "])"
where
vs = jsList show $ V.toList d
jsImageData :: ImageData -> String
jsImageData = showJS
instance JSArg Int where
showJS a = show a
instance JSArg LineEndCap where
showJS = jsLiteralString . show
jsLineEndCap :: LineEndCap -> String
jsLineEndCap = showJS
instance JSArg LineJoinCorner where
showJS = jsLiteralString . show
jsLineJoinCorner :: LineJoinCorner -> String
jsLineJoinCorner = showJS
jsList :: (a -> String) -> [a] -> String
jsList js = concat . intersperse "," . map js
instance JSArg RepeatDirection where
showJS = jsLiteralString . show
jsRepeatDirection :: RepeatDirection -> String
jsRepeatDirection = showJS
instance JSArg Text where
showJS = jsLiteralString . unpack
jsText :: Text -> String
jsText = showJS
instance JSArg TextAnchorAlignment where
showJS = jsLiteralString . show
jsTextAnchorAlignment :: TextAnchorAlignment -> String
jsTextAnchorAlignment = showJS
instance JSArg TextBaselineAlignment where
showJS = jsLiteralString . show
jsTextBaselineAlignment :: TextBaselineAlignment -> String
jsTextBaselineAlignment = showJS
jsLiteralString :: String -> String
jsLiteralString = jsQuoteString . jsEscapeString
jsQuoteString :: String -> String
jsQuoteString s = "\"" ++ s ++ "\""
jsUnicodeChar :: Char -> String
jsUnicodeChar c =
let hex = showHex (ord c) ""
in ('\\':'u': replicate (4 length hex) '0') ++ hex
jsEscapeString :: String -> String
jsEscapeString [] = []
jsEscapeString (c:cs) = case c of
'\\' -> '\\' : '\\' : jsEscapeString cs
'\0' -> jsUnicodeChar '\0' ++ jsEscapeString cs
'\a' -> jsUnicodeChar '\a' ++ jsEscapeString cs
'\b' -> '\\' : 'b' : jsEscapeString cs
'\f' -> '\\' : 'f' : jsEscapeString cs
'\n' -> '\\' : 'n' : jsEscapeString cs
'\r' -> '\\' : 'r' : jsEscapeString cs
'\t' -> '\\' : 't' : jsEscapeString cs
'\v' -> '\\' : 'v' : jsEscapeString cs
'\"' -> '\\' : '\"' : jsEscapeString cs
'\'' -> '\\' : '\'' : jsEscapeString cs
c' | not (isControl c') && isAscii c' -> c' : jsEscapeString cs
c' -> jsUnicodeChar c' ++ jsEscapeString cs