hplayground-0.1.3.1: monadic, reactive Formlets running in the Web browser

Safe HaskellNone
LanguageHaskell98

Haste.HPlay.View

Contents

Description

The haste-hplayground framework. http://github.com/agocorona/hplayground

Synopsis

Documentation

re-exported

widget combinators and modifiers

(<+>) :: (Monad m, FormInput view) => View view m a -> View view m b -> View view m (Maybe a, Maybe b) infixr 2 Source

Join two widgets in the same page the resulting widget, when asked with it, return a 2 tuple of their validation results if both return Noting, the widget return Nothing (invalid).

it has a low infix priority: infixr 2

r <- ask  widget1 <+>  widget2
case r of (Just x, Nothing) -> ..

(**>) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m b infixr 1 Source

The first elem result (even if it is not validated) is discarded, and the secod is returned . This contrast with the applicative operator *> which fails the whole validation if the validation of the first elem fails.

The first element is displayed however, as happens in the case of *> .

Here w's are widgets and r's are returned values

(w1 <* w2) will return Just r1 only if w1 and w2 are validated

(w1 <** w2) will return Just r1 even if w2 is not validated

it has a low infix priority: infixr 1

(<**) :: (Functor m, Monad m, FormInput view) => View view m a -> View view m b -> View view m a infixr 1 Source

The second elem result (even if it is not validated) is discarded, and the first is returned . This contrast with the applicative operator *> which fails the whole validation if the validation of the second elem fails. The second element is displayed however, as in the case of <*. see the <** examples

it has a low infix priority: infixr 1

validate :: Widget a -> (a -> WState Perch IO (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")

firstOf :: [Widget a] -> Widget a Source

Concat a list of widgets of the same type, return a the first validated result

manyOf :: [Widget a] -> Widget [a] Source

from a list of widgets, it return the validated ones.

allOf :: [Widget a] -> Widget [a] Source

like manyOf, but does not validate if one or more of the widgets does not validate

(<<<) :: (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.

(<<) :: (t1 -> t) -> t1 -> t infixr 7 Source

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

(<++) :: (Monad m, Monoid v) => View v m a -> v -> View v m 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 higuer that <<< and most other operators

(<!) :: (FormInput v, Monad m) => View v m a -> Attribs -> View v m a infixl 8 Source

Add attributes to the topmost tag of a widget

it has a fixity infix 8

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. This allow the simultaneous execution of different dynamic behaviours in different page locations at the same page.

basic widgets

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

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

getString :: (StateType (View view m) ~ MFlowState, FormInput view, Monad (View view m), MonadIO m) => Maybe String -> View view m String Source

Display a text box and return a non empty String

inputString :: (StateType (View view m) ~ MFlowState, FormInput view, Monad (View view m), MonadIO m) => Maybe String -> View view m String Source

getInteger :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Integer -> View view m Integer Source

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

getInt :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Int -> View view m Int Source

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

inputInt :: (StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => Maybe Int -> View view m Int Source

getPassword :: (FormInput view, StateType (View view m) ~ MFlowState, MonadIO m) => View view m String Source

Display a password box

setRadio :: (FormInput view, MonadIO m, Typeable a, Eq a, Show a) => a -> String -> View view m (Radio a) Source

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

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

getRadio :: (Monad (View view m), Monad m, Functor m, FormInput view) => [String -> View view m (Radio a)] -> View view m a Source

encloses a set of Radio boxes. Return the option selected

setCheckBox :: (FormInput view, MonadIO m, Typeable a, Show a) => Bool -> a -> View view m (CheckBoxes a) Source

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

getCheckBoxes :: (Monad m, FormInput view) => View view m (CheckBoxes a) -> View view m [a] Source

getTextBox :: (FormInput view, StateType (View view m) ~ MFlowState, MonadIO m, Typeable a, Show a, Read a) => Maybe a -> View view m a Source

getMultilineText :: (FormInput view, MonadIO m) => String -> View view m String Source

Display a multiline text box and return its content

textArea :: (FormInput view, MonadIO m) => String -> View view m String Source

A synonim of getMultilineText

getBool :: (FormInput view, MonadIO m, Functor m, Monad (View view m)) => Bool -> String -> String -> View view m Bool Source

getSelect :: (FormInput view, MonadIO m, Typeable a, Read a) => View view m (MFOption a) -> View view m a Source

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

setOption :: (Monad m, Monad (View view m), Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a) Source

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

setSelectedOption :: (Monad m, Monad (View view m), Show a, Eq a, Typeable a, FormInput view) => a -> view -> View view m (MFOption a) Source

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

wlabel :: (Monad m, FormInput view) => view -> View view m a -> View view m a Source

resetButton :: (FormInput view, Monad m) => String -> View view m () Source

inputReset :: (FormInput view, Monad m) => String -> View view m () Source

submitButton :: (Monad (View view m), StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => String -> View view m String Source

inputSubmit :: (Monad (View view m), StateType (View view m) ~ MFlowState, FormInput view, MonadIO m) => String -> View view m String Source

wbutton :: a -> String -> Widget a Source

active button. When clicked, return the first parameter

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

Present a link. Return the first parameter when clicked

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.

stop :: Widget a Source

a sinonym of noWidget that can be used in a monadic expression in the View monad. it stop the computation in the Widget monad.

wraw :: Perch -> Widget () Source

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

isEmpty :: Widget a -> Widget Bool Source

True if the widget has no valid input

out of flow updates

at :: String -> 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 internal(Insert) or external(Outer) content depending on the update method.

at' :: String -> UpdateMethod -> Widget a -> Widget a Source

A generalized version of at that include the widget rendering at the elements that meet the selector criteria (the first parameter) in the style of jQuery. the selector can match classes etc not only identifiers.

Session data storage

getSessionData :: (StateType m ~ MFlowState, MonadState m, Typeable a) => m (Maybe a) Source

Get the session data of the desired type if there is any.

getSData :: Typeable a => Widget a Source

getSessionData specialized for the View monad. if Nothing, the monadic computation does not continue. getSData is a widget that does not validate when there is no data of that type in the session.

setSessionData :: (MonadState m, Typeable * a, (~) * (StateType m) MFlowState) => a -> m () Source

setSessionData :: (StateType m ~ MFlowState, Typeable a) => a -> m ()

setSData :: (StateType m ~ MFlowState, MonadState m, Typeable a) => a -> m () Source

a shorter name for setSessionData

delSessionData :: (MonadState m, Typeable * a, (~) * (StateType m) MFlowState) => a -> m () Source

reactive and events

class IsEvent a b | a -> b where Source

Methods

eventName :: a -> String Source

buildHandler :: a -> IO () -> b Source

Instances

IsEvent (Event m a) a 

data EventData Source

Constructors

EventData 

Fields

evName :: String
 
evData :: EvData
 

data EvData Source

Constructors

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

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

triggers the event when it happens in the widget.

What happens then?

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

2) with the result of this reevaluaution, executes the rest of the monadic computation

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

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

Neither the computation nor the tree in the upstream flow is touched. (unless you use out of stream directives, like at)

monadic computations inside monadic computations are executed following recursively the steps mentioned above. So an event in a component deep down could or could not trigger the reexecution of the rest of the whole.

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

A shorter synonym for raiseEvent

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

A shorter and smoother synonym for raiseEvent

react :: IsEvent event callback => Widget a -> event -> Widget a Source

A professional synonym for raiseEvent

pass :: Perch -> Event IO b -> 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

continueIf :: Bool -> a -> Widget a Source

return empty and the monadic computation stop if the condition is false. If true, return the second parameter.

wtimeout :: Int -> Widget () -> Widget () Source

executes a widget each t milliseconds until it validates and return ()

data Event m a :: (* -> *) -> * -> * where

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) 
IsEvent (Event m a) a 

running it

runWidget :: Widget b -> Elem -> IO (Maybe b) Source

run the widget as the content of a DOM element the new rendering is added to the element

runWidgetId :: Widget b -> ElemID -> IO (Maybe b) Source

run the widget as the content of a DOM element, the id is passed as parameter. All the content of the element is erased previously and it is substituted by the new rendering

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

run the widget as the body of the HTML

addHeader :: Perch -> IO () Source

add a header in the header tag

static :: Monad m => View v m a -> View v m a Source

To produce updates, each line of html produced by a "do" sequence in the Widget monad is included within a span tag. When the line is reexecuted after a event, the span is updated with the new rendering.

static tell to the rendering that this widget does not change, so the extra span tag for each line in the sequence and the rewriting is not necessary. Thus the size of the HTML and the performance is improved.

dynamic :: Monad m => View v m a -> View v m a Source

override static locally to permit dynamic effects inside a static widget. It is useful when a monadic Widget computation which perform no rendering changes has a to do some update:

launchMissiles= static $ do
   t <- armLauncher
   c <- fixTarget t
   f <- fire c
   dynamic $ displayUpdate t c f
   return ()

Perch is reexported

communications

ajax :: (JSType a, JSType b, JSType c, Typeable c) => Method -> URL -> [(a, b)] -> Widget (Maybe c) Source

Invoke AJAX. ToJSString is a class coverter to-from JavaScript strings `(a,b)` are the lists of parameters, a is normally String or JSString. JSON is also supported for b and c. If you want to handle your data types, make a instance of JSType

Note the de-inversion of control. There is no callback.

ajax can be combined with other Widgets using monadic, applicative or alternative combinators.

data Method :: *

Constructors

GET 
POST 

Instances

low level and internals

getNextId :: (StateType m ~ MFlowState, MonadState m) => m String Source

get the next ideitifier that will be created by genNewId

genNewId :: (StateType m ~ MFlowState, MonadState m) => m String Source

Generate a new string. Useful for creating tag identifiers and other attributes.

if the page is refreshed, the identifiers generated are the same.

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 :: (FormInput view, StateType (View view m) ~ MFlowState, MonadIO m, Typeable a, Show a, Read a) => Maybe String -> String -> Maybe a -> View view m a 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 :: String -> view Source

fromStrNoEncode :: String -> view Source

ftag :: String -> view -> view Source

inred :: view -> view Source

flink :: String -> view -> view Source

flink1 :: String -> view Source

finput :: Name -> Type -> Value -> Checked -> OnClick -> view Source

ftextarea :: String -> String -> view Source

fselect :: String -> view -> view Source

foption :: String -> view -> Bool -> view Source

foption1 :: String -> Bool -> view Source

formAction :: String -> String -> view -> view Source

attrs :: view -> Attribs -> view Source

Instances

newtype View v m a Source

Constructors

View 

Fields

runView :: WState v m (FormElm v a)
 

Instances

Attributable (Widget a) 
Monoid view => MonadTrans (View view) 
(Monoid view, Functor m, Monad m, Monad (View view m)) => Alternative (View view m) 
Monad (View Perch IO) 
(Monad m, Functor m, Monad (View view m)) => Functor (View view m) 
(Monoid view, Functor m, Monad m, Monad (View view m)) => Applicative (View view m) 
(FormInput view, Monad (View view m), MonadIO m) => MonadIO (View view m) 
(FormInput view, Monad m, Monad (View view m)) => MonadState (View view m) 
(FormInput v, Monad (View v m), Monad m, Functor m, Monoid a) => Monoid (View v m a) 
type StateType (View view m) = MFlowState 

data FormElm view a Source

Constructors

FormElm view (Maybe a) 

Instances

Functor (FormElm view) 
Monoid view => Monoid (FormElm view a) 

data EventF Source

Constructors

forall b c . EventF (IO (Maybe b)) (b -> IO (Maybe c)) 

data MFlowState Source

Constructors

MFlowState 

Fields

mfPrefix :: String
 
mfSequence :: Int
 
needForm :: NeedForm
 
process :: EventF
 
fixed :: Bool
 
lastEvent :: Dynamic
 
mfData :: Map TypeRep SData