haste-compiler-0.4.4.3: Haskell To ECMAScript compiler

Safe HaskellNone
LanguageHaskell98

Haste

Description

Haste's companion to the Prelude.

Note that this module should *not* be imported together with Haste.App, which provides the same functionality but slightly modified for automatic program slicing.

Synopsis

Documentation

data JSString Source

JSStrings are represented as normal strings server-side; should probably be changed to ByteString or Text.

type JSAny = Ptr Any Source

class GenericCallback a m where Source

Associated Types

type CB a Source

Methods

mkcb :: (m () -> IO ()) -> a -> CB a Source

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.

alert :: MonadIO m => String -> m () Source

Javascript alert() function.

prompt :: MonadIO m => String -> m String Source

Javascript prompt() function.

eval :: MonadIO m => JSString -> m JSString Source

Javascript eval() function.

writeLog :: MonadIO m => String -> m () Source

Use console.log to write a message.

catJSStr :: JSString -> [JSString] -> JSString Source

Concatenate a series of JSStrings using the specified separator.

class JSNum a where Source

(Almost) all numeric types can be efficiently converted to and from Double, which is the internal representation for most of them.

convert :: (JSNum a, JSNum b) => a -> b Source

module Haste.DOM

class GenericCallback a m where Source

Associated Types

type CB a Source

Methods

mkcb :: (m () -> IO ()) -> a -> CB a Source

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.

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 Bool Source

Set a callback for the given event.

setCallback' :: (ToConcurrent a, MonadIO m) => Elem -> Event CIO a -> Async a -> m Bool Source

Like setCallback, but takes a callback in the CIO monad instead of IO.

newtype JSFun a Source

Constructors

JSFun (Ptr a) 

mkCallback :: a -> JSFun a Source

Turn a computation into a callback that can be passed to a JS function.

data Event m a where Source

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 ()) 
OnSubmit :: Event m (m ()) 
OnWheel :: Event m ((Int, Int) -> (Double, Double, Double) -> m ()) 

Instances

Eq (Event m a) 
Ord (Event m a) 

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.

class Callback a where Source

Methods

constCallback :: IO () -> a Source

Instances

Callback (IO ()) 
Callback (a -> IO ()) 

onEvent :: MonadIO m => Elem -> Event IO a -> a -> m Bool Source

Friendlier name for setCallback.

onEvent' :: (ToConcurrent a, MonadIO m) => Elem -> Event CIO a -> Async a -> m Bool Source

Friendlier name for setCallback'.

evtName :: IsString s => Event m a -> s Source

The name of a given event.

class Random a where Source

Minimal complete definition

randomR

Methods

randomR :: (a, a) -> Seed -> (a, Seed) Source

Generate a pseudo random number between a lower (inclusive) and higher (exclusive) bound.

randomRs :: (a, a) -> Seed -> [a] Source

next :: Seed -> Seed Source

Generate the next seed in the sequence.

mkSeed :: Int -> Seed Source

Create a new seed from an integer.

newSeed :: MonadIO m => m Seed Source

Generate a new seed using Javascript's PRNG.

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.

setHash :: MonadIO m => String -> m () Source

Set the hash part of the current URL.

getHash :: MonadIO m => m String Source

Read the hash part of the currunt URL.

setHash' :: MonadIO m => JSString -> m () Source

Set the hash part of the current URL - JSString version.

getHash' :: MonadIO m => m JSString Source

Read the hash part of the currunt URL - JSString version.