Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data Context
- data Canvas
- data Image
- data TextAlign
- data TextBaseline
- = Top
- | Hanging
- | Middle
- | Alphabetic
- | Ideographic
- | Bottom
- data LineCap
- data LineJoin
- data Repeat
- data Gradient
- data Pattern
- create :: Int -> Int -> IO Canvas
- unsafeToCanvas :: JSVal -> Canvas
- toCanvas :: JSVal -> Maybe Canvas
- getContext :: Canvas -> IO Context
- save :: Context -> IO ()
- restore :: Context -> IO ()
- scale :: Double -> Double -> Context -> IO ()
- rotate :: Double -> Context -> IO ()
- translate :: Double -> Double -> Context -> IO ()
- transform :: Double -> Double -> Double -> Double -> Double -> Double -> Context -> IO ()
- setTransform :: Double -> Double -> Double -> Double -> Double -> Double -> Context -> IO ()
- fill :: Context -> IO ()
- fillRule :: JSString -> Context -> IO ()
- stroke :: Context -> IO ()
- beginPath :: Context -> IO ()
- closePath :: Context -> IO ()
- clip :: Context -> IO ()
- moveTo :: Double -> Double -> Context -> IO ()
- lineTo :: Double -> Double -> Context -> IO ()
- quadraticCurveTo :: Double -> Double -> Double -> Double -> Context -> IO ()
- bezierCurveTo :: Double -> Double -> Double -> Double -> Double -> Double -> Context -> IO ()
- arc :: Double -> Double -> Double -> Double -> Double -> Bool -> Context -> IO ()
- arcTo :: Double -> Double -> Double -> Double -> Double -> Context -> IO ()
- rect :: Double -> Double -> Double -> Double -> Context -> IO ()
- isPointInPath :: Double -> Double -> Context -> IO ()
- fillStyle :: Int -> Int -> Int -> Double -> Context -> IO ()
- strokeStyle :: Int -> Int -> Int -> Double -> Context -> IO ()
- globalAlpha :: Double -> Context -> IO ()
- lineJoin :: LineJoin -> Context -> IO ()
- lineCap :: LineCap -> Context -> IO ()
- lineWidth :: Double -> Context -> IO ()
- setLineDash :: JSArray -> Context -> IO ()
- lineDashOffset :: Double -> Context -> IO ()
- miterLimit :: Double -> Context -> IO ()
- fillText :: JSString -> Double -> Double -> Context -> IO ()
- strokeText :: JSString -> Double -> Double -> Context -> IO ()
- font :: JSString -> Context -> IO ()
- measureText :: JSString -> Context -> IO Double
- textAlign :: TextAlign -> Context -> IO ()
- textBaseline :: TextBaseline -> Context -> IO ()
- fillRect :: Double -> Double -> Double -> Double -> Context -> IO ()
- strokeRect :: Double -> Double -> Double -> Double -> Context -> IO ()
- clearRect :: Double -> Double -> Double -> Double -> Context -> IO ()
- drawImage :: Image -> Int -> Int -> Int -> Int -> Context -> IO ()
- width :: Canvas -> IO Int
- setWidth :: Int -> Canvas -> IO ()
- height :: Canvas -> IO Int
- setHeight :: Int -> Canvas -> IO ()
Documentation
Instances
Enum TextAlign Source # | |
Defined in JavaScript.Web.Canvas succ :: TextAlign -> TextAlign # pred :: TextAlign -> TextAlign # fromEnum :: TextAlign -> Int # enumFrom :: TextAlign -> [TextAlign] # enumFromThen :: TextAlign -> TextAlign -> [TextAlign] # enumFromTo :: TextAlign -> TextAlign -> [TextAlign] # enumFromThenTo :: TextAlign -> TextAlign -> TextAlign -> [TextAlign] # | |
Eq TextAlign Source # | |
Data TextAlign Source # | |
Defined in JavaScript.Web.Canvas gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextAlign -> c TextAlign gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextAlign toConstr :: TextAlign -> Constr dataTypeOf :: TextAlign -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextAlign) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextAlign) gmapT :: (forall b. Data b => b -> b) -> TextAlign -> TextAlign gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextAlign -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextAlign -> r gmapQ :: (forall d. Data d => d -> u) -> TextAlign -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> TextAlign -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextAlign -> m TextAlign gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextAlign -> m TextAlign gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextAlign -> m TextAlign | |
Show TextAlign Source # | |
data TextBaseline Source #
Instances
Instances
Enum LineCap Source # | |
Eq LineCap Source # | |
Data LineCap Source # | |
Defined in JavaScript.Web.Canvas gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LineCap -> c LineCap gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LineCap dataTypeOf :: LineCap -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LineCap) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LineCap) gmapT :: (forall b. Data b => b -> b) -> LineCap -> LineCap gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LineCap -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LineCap -> r gmapQ :: (forall d. Data d => d -> u) -> LineCap -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> LineCap -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> LineCap -> m LineCap gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LineCap -> m LineCap gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LineCap -> m LineCap | |
Show LineCap Source # | |
Instances
Enum LineJoin Source # | |
Eq LineJoin Source # | |
Show LineJoin Source # | |
Instances
Enum Repeat Source # | |
Defined in JavaScript.Web.Canvas | |
Eq Repeat Source # | |
Data Repeat Source # | |
Defined in JavaScript.Web.Canvas gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Repeat -> c Repeat gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Repeat dataTypeOf :: Repeat -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Repeat) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Repeat) gmapT :: (forall b. Data b => b -> b) -> Repeat -> Repeat gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Repeat -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Repeat -> r gmapQ :: (forall d. Data d => d -> u) -> Repeat -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Repeat -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Repeat -> m Repeat gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Repeat -> m Repeat gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Repeat -> m Repeat | |
Ord Repeat Source # | |
Show Repeat Source # | |
unsafeToCanvas :: JSVal -> Canvas Source #
setTransform :: Double -> Double -> Double -> Double -> Double -> Double -> Context -> IO () Source #
bezierCurveTo :: Double -> Double -> Double -> Double -> Double -> Double -> Context -> IO () Source #
textBaseline :: TextBaseline -> Context -> IO () Source #