axiom-0.4.3: Web EDSL running over transient running in browsers and server nodes

Safe HaskellNone
LanguageHaskell2010

GHCJS.HPlay.View

Contents

Synopsis

Documentation

newtype Widget a Source #

Constructors

Widget 

Fields

Instances

Monad Widget Source # 

Methods

(>>=) :: Widget a -> (a -> Widget b) -> Widget b #

(>>) :: Widget a -> Widget b -> Widget b #

return :: a -> Widget a #

fail :: String -> Widget a #

Functor Widget Source # 

Methods

fmap :: (a -> b) -> Widget a -> Widget b #

(<$) :: a -> Widget b -> Widget a #

Applicative Widget Source # 

Methods

pure :: a -> Widget a #

(<*>) :: Widget (a -> b) -> Widget a -> Widget b #

(*>) :: Widget a -> Widget b -> Widget b #

(<*) :: Widget a -> Widget b -> Widget a #

Alternative Widget Source # 

Methods

empty :: Widget a #

(<|>) :: Widget a -> Widget a -> Widget a #

some :: Widget a -> Widget [a] #

many :: Widget a -> Widget [a] #

MonadPlus Widget Source # 

Methods

mzero :: Widget a #

mplus :: Widget a -> Widget a -> Widget a #

MonadIO Widget Source # 

Methods

liftIO :: IO a -> Widget a #

AdditionalOperators Widget Source # 

Methods

(**>) :: Widget a -> Widget b -> Widget b #

(<**) :: Widget a -> Widget b -> Widget a #

atEnd' :: Widget a -> Widget b -> Widget a #

(<***) :: Widget a -> Widget b -> Widget a #

atEnd :: Widget a -> Widget b -> Widget a #

MonadState EventF Widget Source # 

Methods

get :: Widget EventF #

put :: EventF -> Widget () #

state :: (EventF -> (a, EventF)) -> Widget a #

(Eq a, Num a) => Num (Widget a) Source # 

Methods

(+) :: Widget a -> Widget a -> Widget a #

(-) :: Widget a -> Widget a -> Widget a #

(*) :: Widget a -> Widget a -> Widget a #

negate :: Widget a -> Widget a #

abs :: Widget a -> Widget a #

signum :: Widget a -> Widget a #

fromInteger :: Integer -> Widget a #

Monoid a => Monoid (Widget a) Source # 

Methods

mempty :: Widget a #

mappend :: Widget a -> Widget a -> Widget a #

mconcat :: [Widget a] -> Widget a #

Attributable (Widget a) Source # 

Methods

(!) :: Widget a -> Attribute -> Widget a #

Running it

runBody :: Widget a -> IO (Maybe a) Source #

run the widget as the body of the HTML. It adds the rendering to the body of the document.

Use only for pure client-side applications, like the ones of http://http://tryplayg.herokuapp.com

addHeader :: Perch -> IO () Source #

add a header in the header tag

render :: Widget a -> TransIO a Source #

executes the computation and add the effect of "hanging" the generated rendering from the one generated by the previous render sentence, or from the body of the document, if there isn't any. If an event happens within the render parameter, it deletes the rendering of all subsequent ones. so that the sucessive sequence of render in the code will reconstruct them again. However the rendering of elements combined with <|> or <> or <*> are independent. This allows for full dynamic and composable client-side Web apps.

addSData :: (MonadState EventF m, Typeable a, Monoid a) => a -> m () Source #

Widget Combinators and Modifiers

(<<) :: (Perch -> Perch) -> Perch -> Perch infixr 7 Source #

A parameter application with lower priority than ($) and direct function application

(<<<) :: (Perch -> Perch) -> Widget a -> Widget a infixr 5 Source #

Enclose Widgets within some formating. view is intended to be instantiated to a particular format

NOTE: It has a infix priority : infixr 5 less than the one of ++> and <++ of the operators, so use parentheses when appropriate, unless the we want to enclose all the widgets in the right side. Most of the type errors in the DSL are due to the low priority of this operator.

(<!) :: Widget a -> Attribs -> Widget a infixl 8 Source #

Add attributes to the topmost tag of a widget

(<++) :: Widget a -> Perch -> Widget a infixr 6 Source #

Append formatting code to a widget

 getString "hi" <++ H1 << "hi there"

It has a infix prority: infixr 6 higuer that <<< and most other operators

(++>) :: Perch -> Widget a -> Widget a infixr 6 Source #

Prepend formatting code to a widget

bold "enter name" ++ getString Nothing

It has a infix prority: infixr 6 higher that <<< and most other operators

validate :: Widget a -> (a -> StateIO (Maybe Perch)) -> Widget a Source #

Validates a form or widget result against a validating procedure

getOdd= getInt Nothing validate (x -> return $ if mod x 2==0 then  Nothing else Just "only odd numbers, please")

wcallback :: Widget a -> (a -> Widget b) -> Widget b Source #

It is a callback in the view monad. The rendering of the second parameter substitutes the rendering of the first paramenter when the latter validates without afecting the rendering of other widgets.

Basic Widgets

option :: (Typeable b, Show b) => b -> String -> Widget b Source #

use this instead of option when runing in the browser

wprint :: ToElem a => a -> Widget () Source #

show something enclosed in the pre tag, so ASCII formatting chars are honored

getString :: Maybe String -> Widget String Source #

Display a text box and return a non empty String

getInteger :: Maybe Integer -> Widget Integer Source #

Display a text box and return an Integer (if the value entered is not an Integer, fails the validation)

getInt :: Maybe Int -> Widget Int Source #

Display a text box and return a Int (if the value entered is not an Int, fails the validation)

getPassword :: Widget String Source #

Display a password box

setRadio :: (Typeable a, Eq a, Show a) => a -> Widget (Radio a) Source #

Implement a radio button the parameter is the name of the radio group

setRadioActive :: (Typeable a, Eq a, Show a) => a -> Widget (Radio a) Source #

getRadio :: Monoid a => [Widget (Radio a)] -> Widget a Source #

encloses a set of Radio boxes. Return the option selected

setCheckBox :: (Typeable a, Show a) => Bool -> a -> Widget (CheckBoxes a) Source #

Display a text box and return the value entered if it is readable( Otherwise, fail the validation)

getTextBox :: (Typeable a, Show a, Read a) => Maybe a -> Widget a Source #

getMultilineText :: JSString -> Widget String Source #

Display a multiline text box and return its content

textArea :: JSString -> Widget String Source #

A synonim of getMultilineText

getSelect :: (Typeable a, Read a, Show a) => Widget (MFOption a) -> Widget a Source #

Display a dropdown box with the options in the first parameter is optionally selected . It returns the selected option.

setOption :: (Show a, Eq a, Typeable a) => a -> Perch -> Widget (MFOption a) Source #

Set the option for getSelect. Options are concatenated with <|>

setSelectedOption :: (Show a, Eq a, Typeable a) => a -> Perch -> Widget (MFOption a) Source #

Set the selected option for getSelect. Options are concatenated with <|>

resetButton :: JSString -> Widget () Source #

inputReset :: JSString -> Widget () Source #

submitButton :: (Read a, Show a, Typeable a) => a -> Widget a Source #

inputSubmit :: (Read a, Show a, Typeable a) => a -> Widget a Source #

wbutton :: a -> JSString -> Widget a Source #

active button. When clicked, return the first parameter

wlink :: (Show a, Typeable a) => a -> Perch -> Widget a Source #

Present a link. It return the first parameter and execute the continuation when it is clicked.

It also update the path in the URL.

tlink :: (Show a, Read a, Typeable a) => a -> Perch -> Widget a Source #

Present a link. Return the first parameter when clicked

template link. Besides the wlink behaviour, it loads the page from the server if there is any

the page many have been saved with edit

noWidget :: Widget a Source #

Empty widget that does not validate. May be used as "empty boxes" inside larger widgets.

It returns a non valid value.

wraw :: Perch -> Widget () Source #

Render raw view formatting. It is useful for displaying information.

rawHtml :: Perch -> Widget () Source #

wraw synonym

isEmpty :: Widget a -> Widget Bool Source #

True if the widget has no valid input

Events

Out of Flow Updates

at :: JSString -> UpdateMethod -> Widget a -> Widget a Source #

Run the widget as the content of the element with the given id. The content can be appended, prepended to the previous content or it can be the only content depending on the update method.

at' :: JSString -> UpdateMethod -> Cloud a -> Cloud a Source #

Reactive and Events

class Typeable a => IsEvent a where Source #

Minimal complete definition

eventName, buildHandler

Methods

eventName :: a -> JSString Source #

buildHandler :: Elem -> a -> (EventData -> IO ()) -> IO () Source #

Instances

data EventData Source #

Constructors

EventData 

Fields

data EvData Source #

Constructors

NoData 
Click Int (Int, Int) 
Mouse (Int, Int) 
MouseOut 
Key Int 

Instances

raiseEvent :: IsEvent event => Widget a -> event -> Widget a Source #

triggers the event that happens in a widget. The effects are the following:

1)The event reexecutes the monadic sentence where the widget is, (with no re-rendering)

2) with the result of this reevaluaution of 1), the rest of the monadic computation is executed

3) update the DOM tree with the rendering generated by the reevaluation of 2).

As usual, If one step of the monadic computation return empty (stop), the reevaluation finish So the effect of an event can be restricted as much as you may need.

The part of the monadic expression that is before the event is not evaluated and his rendering is untouched. (but, at any moment, you can choose the element to be updated in the page using at)

fire :: IsEvent event => Widget a -> event -> Widget a Source #

A shorter synonym for raiseEvent

wake :: IsEvent event => Widget a -> event -> Widget a Source #

A shorter and smoother synonym for raiseEvent

pass :: IsEvent event => Perch -> event -> Widget EventData Source #

pass trough only if the event is fired in this DOM element. Otherwise, if the code is executing from a previous event, the computation will stop

Low-level and Internals

type ElemID = JSString Source #

class (Monoid view, Typeable view) => FormInput view where Source #

Minimal interface for defining the basic form and link elements. The core of MFlow is agnostic about the rendering package used. Every formatting (either HTML or not) used with MFlow must have an instance of this class. See "MFlow.Forms.Blaze.Html for the instance for blaze-html" MFlow.Forms.XHtml for the instance for Text.XHtml and MFlow.Forms.HSP for the instance for Haskell Server Pages.

Methods

fromStr :: JSString -> view Source #

fromStrNoEncode :: String -> view Source #

ftag :: JSString -> view -> view Source #

inred :: view -> view Source #

flink :: JSString -> view -> view Source #

flink1 :: JSString -> view Source #

finput :: Name -> Type -> Value -> Checked -> OnClick1 -> view Source #

ftextarea :: JSString -> JSString -> view Source #

fselect :: JSString -> view -> view Source #

foption :: JSString -> view -> Bool -> view Source #

foption1 :: JSString -> Bool -> view Source #

formAction :: JSString -> JSString -> view -> view Source #

attrs :: view -> Attribs -> view Source #

Instances

FormInput Perch Source # 

Methods

fromStr :: JSString -> Perch Source #

fromStrNoEncode :: String -> Perch Source #

ftag :: JSString -> Perch -> Perch Source #

inred :: Perch -> Perch Source #

flink :: JSString -> Perch -> Perch Source #

flink1 :: JSString -> Perch Source #

finput :: Name -> Type -> Value -> Checked -> OnClick1 -> Perch Source #

ftextarea :: JSString -> JSString -> Perch Source #

fselect :: JSString -> Perch -> Perch Source #

foption :: JSString -> Perch -> Bool -> Perch Source #

foption1 :: JSString -> Bool -> Perch Source #

formAction :: JSString -> JSString -> Perch -> Perch Source #

attrs :: Perch -> Attribs -> Perch Source #

getNextId :: MonadState EventF m => m JSString Source #

get the next ideitifier that will be created by genNewId

genNewId :: (MonadState EventF m, MonadIO m) => m JSString Source #

continuePerch :: Widget a -> ElemID -> Widget a Source #

when creating a complex widget with many tags, this call indentifies which tag will receive the attributes of the (!) operator.

getParam :: (Typeable a, Show a, Read a) => Maybe JSString -> JSString -> Maybe a -> Widget a Source #

getCont :: TransIO EventF #

Get the continuation context: closure, continuation, state, child threads etc

runCont :: EventF -> StateIO (Maybe a) #

Run the closure and the continuation using the state data of the calling thread

elemById :: MonadIO m => JSString -> m (Maybe Elem) Source #

withElem :: ElemID -> (Elem -> IO a) -> IO a Source #

getProp :: Elem -> JSString -> IO JSString Source #

setProp :: Elem -> JSString -> JSString -> IO () Source #

alert :: JSString -> IO () Source #

fromJSString :: (Typeable a, Read a) => JSString -> a Source #

toJSString :: (Show a, Typeable a) => a -> JSString Source #

Re-exported

data CheckBoxes a Source #

Constructors

CheckBoxes [a] 

edit :: Cloud a -> Cloud a Source #

edit and save the rendering of the widgets.

The edited content may be saved to a file with th current route by the save option of the editor. tlink will load this page. Also when this route is requested, the server will return this page.