Safe Haskell | None |
---|
Haste
- data JSString
- type JSAny = Ptr Any
- type URL = String
- class GenericCallback a m where
- alert :: MonadIO m => String -> m ()
- prompt :: MonadIO m => String -> m String
- eval :: MonadIO m => JSString -> m JSString
- writeLog :: MonadIO m => String -> m ()
- catJSStr :: JSString -> [JSString] -> JSString
- fromJSStr :: JSString -> String
- class JSType a where
- toJSString :: a -> JSString
- fromJSString :: JSString -> Maybe a
- class JSNum a where
- toNumber :: a -> Double
- fromNumber :: Double -> a
- toString :: JSType a => a -> String
- fromString :: JSType a => String -> Maybe a
- convert :: (JSNum a, JSNum b) => a -> b
- module Haste.DOM
- class GenericCallback a m where
- toCallback :: (Monad m, GenericCallback a m) => a -> m (CB a)
- setCallback :: MonadIO m => Elem -> Event IO a -> a -> m Bool
- setCallback' :: (ToConcurrent a, MonadIO m) => Elem -> Event CIO a -> Async a -> m Bool
- newtype JSFun a = JSFun (Ptr a)
- mkCallback :: a -> JSFun a
- data Event m a where
- OnLoad :: Event m (m ())
- OnUnload :: Event m (m ())
- OnChange :: Event m (m ())
- OnFocus :: Event m (m ())
- OnBlur :: Event m (m ())
- OnMouseMove :: Event m ((Int, Int) -> m ())
- OnMouseOver :: Event m ((Int, Int) -> m ())
- OnMouseOut :: Event m (m ())
- OnClick :: Event m (Int -> (Int, Int) -> m ())
- OnDblClick :: Event m (Int -> (Int, Int) -> m ())
- OnMouseDown :: Event m (Int -> (Int, Int) -> m ())
- OnMouseUp :: Event m (Int -> (Int, Int) -> m ())
- OnKeyPress :: Event m (Int -> m ())
- OnKeyUp :: Event m (Int -> m ())
- OnKeyDown :: Event m (Int -> m ())
- setTimeout :: MonadIO m => Int -> IO () -> m ()
- setTimeout' :: MonadIO m => Int -> CIO () -> m ()
- class Callback a where
- constCallback :: IO () -> a
- onEvent :: MonadIO m => Elem -> Event IO a -> a -> m Bool
- onEvent' :: (ToConcurrent a, MonadIO m) => Elem -> Event CIO a -> Async a -> m Bool
- jsSetCB :: Elem -> JSString -> JSFun a -> IO Bool
- jsSetTimeout :: Int -> JSFun a -> IO ()
- evtName :: IsString s => Event m a -> s
- class Random a where
- data Seed
- next :: Seed -> Seed
- mkSeed :: Int -> Seed
- newSeed :: MonadIO m => m Seed
- onHashChange :: (MonadIO m, GenericCallback (m ()) m, CB (m ()) ~ IO ()) => (String -> String -> m ()) -> m ()
- onHashChange' :: (MonadIO m, GenericCallback (m ()) m, CB (m ()) ~ IO ()) => (JSString -> JSString -> m ()) -> m ()
- setHash :: MonadIO m => String -> m ()
- getHash :: MonadIO m => m String
- setHash' :: MonadIO m => JSString -> m ()
- getHash' :: MonadIO m => m JSString
Documentation
JSStrings are represented as normal strings server-side; should probably be changed to ByteString or Text.
class GenericCallback a m whereSource
Methods
mkcb :: (m () -> IO ()) -> a -> CB aSource
Build a callback from an IOfier and a function.
mkIOfier :: a -> m (m () -> IO ())Source
Never evaluate the first argument to mkIOfier, it's only there to fix the types.
Instances
GenericCallback (IO ()) IO | |
GenericCallback (CIO ()) CIO | |
GenericCallback (Client ()) Client | |
GenericCallback b m => GenericCallback (a -> b) m |
catJSStr :: JSString -> [JSString] -> JSStringSource
Concatenate a series of JSStrings using the specified separator.
(Almost) all numeric types can be efficiently converted to and from Double, which is the internal representation for most of them.
fromString :: JSType a => String -> Maybe aSource
module Haste.DOM
class GenericCallback a m whereSource
Methods
mkcb :: (m () -> IO ()) -> a -> CB aSource
Build a callback from an IOfier and a function.
mkIOfier :: a -> m (m () -> IO ())Source
Never evaluate the first argument to mkIOfier, it's only there to fix the types.
Instances
GenericCallback (IO ()) IO | |
GenericCallback (CIO ()) CIO | |
GenericCallback (Client ()) Client | |
GenericCallback b m => GenericCallback (a -> b) m |
toCallback :: (Monad m, GenericCallback a m) => a -> m (CB a)Source
Turn a function of type a -> ... -> m () into a function of type a -> ... -> IO (), for use with generic JS callbacks.
setCallback :: MonadIO m => Elem -> Event IO a -> a -> m BoolSource
Set a callback for the given event.
setCallback' :: (ToConcurrent a, MonadIO m) => Elem -> Event CIO a -> Async a -> m BoolSource
Like setCallback
, but takes a callback in the CIO monad instead of IO.
mkCallback :: a -> JSFun aSource
Turn a computation into a callback that can be passed to a JS function.
These constructors correspond to their namesake DOM events. Mouse related callbacks receive the coordinates of the mouse pointer at the time the event was fired, relative to the top left corner of the element that fired the event. The click events also receive the mouse button that was pressed.
The key updownpress events receive the character code of the key that was pressed.
Constructors
OnLoad :: Event m (m ()) | |
OnUnload :: Event m (m ()) | |
OnChange :: Event m (m ()) | |
OnFocus :: Event m (m ()) | |
OnBlur :: Event m (m ()) | |
OnMouseMove :: Event m ((Int, Int) -> m ()) | |
OnMouseOver :: Event m ((Int, Int) -> m ()) | |
OnMouseOut :: Event m (m ()) | |
OnClick :: Event m (Int -> (Int, Int) -> m ()) | |
OnDblClick :: Event m (Int -> (Int, Int) -> m ()) | |
OnMouseDown :: Event m (Int -> (Int, Int) -> m ()) | |
OnMouseUp :: Event m (Int -> (Int, Int) -> m ()) | |
OnKeyPress :: Event m (Int -> m ()) | |
OnKeyUp :: Event m (Int -> m ()) | |
OnKeyDown :: Event m (Int -> m ()) |
setTimeout :: MonadIO m => Int -> IO () -> m ()Source
Wrapper for window.setTimeout; execute the given computation after a delay given in milliseconds.
setTimeout' :: MonadIO m => Int -> CIO () -> m ()Source
Like setTimeout
, but takes a callback in the CIO monad instead of IO.
Methods
constCallback :: IO () -> aSource
onEvent' :: (ToConcurrent a, MonadIO m) => Elem -> Event CIO a -> Async a -> m BoolSource
Friendlier name for setCallback'
.
jsSetTimeout :: Int -> JSFun a -> IO ()Source
onHashChange :: (MonadIO m, GenericCallback (m ()) m, CB (m ()) ~ IO ()) => (String -> String -> m ()) -> m ()Source
Register a callback to be run whenever the URL hash changes. The two arguments of the callback are the new and old hash respectively.
onHashChange' :: (MonadIO m, GenericCallback (m ()) m, CB (m ()) ~ IO ()) => (JSString -> JSString -> m ()) -> m ()Source
JSString version of onHashChange
.