threepenny-editors-0.5.5: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors.Types

Contents

Synopsis

GenericWidgets

data GenericWidget control a Source #

Constructors

GenericWidget 

Fields

Instances

Bifunctor GenericWidget Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> GenericWidget a c -> GenericWidget b d #

first :: (a -> b) -> GenericWidget a c -> GenericWidget b c #

second :: (b -> c) -> GenericWidget a b -> GenericWidget a c #

Functor (GenericWidget control) Source # 

Methods

fmap :: (a -> b) -> GenericWidget control a -> GenericWidget control b #

(<$) :: a -> GenericWidget control b -> GenericWidget control a #

Widget el => Widget (GenericWidget el a) Source # 

Methods

getElement :: GenericWidget el a -> Element #

Renderable el => Renderable (GenericWidget el a) Source # 

Editors

newtype Editor outer widget inner Source #

An editor for values of type inner inside a datatype outer realized by a widget.

All the three type arguments are functorial, but outer is contravariant, so Editor is a Biapplicative functor and a Profunctor (via dimapE).

Biapplicative allows to compose editors on both their widget and inner structure. When widget is monoidal, widget composition is implicit and Applicative suffices.

Profunctor allows to apply an inner editor to an outer datatype.

Once created, an Editor yields a tuple of an widget and a Tidings inner which can be integrated in a threepenny app.

Constructors

Editor 

Fields

Instances

Bifunctor (Editor a) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Editor a a c -> Editor a b d #

first :: (a -> b) -> Editor a a c -> Editor a b c #

second :: (b -> c) -> Editor a a b -> Editor a a c #

Biapplicative (Editor a) Source # 

Methods

bipure :: a -> b -> Editor a a b #

(<<*>>) :: Editor a (a -> b) (c -> d) -> Editor a a c -> Editor a b d #

(*>>) :: Editor a a b -> Editor a c d -> Editor a c d #

(<<*) :: Editor a a b -> Editor a c d -> Editor a a b #

Functor (Editor a el) Source # 

Methods

fmap :: (a -> b) -> Editor a el a -> Editor a el b #

(<$) :: a -> Editor a el b -> Editor a el a #

Monoid el => Applicative (Editor a el) Source # 

Methods

pure :: a -> Editor a el a #

(<*>) :: Editor a el (a -> b) -> Editor a el a -> Editor a el b #

(*>) :: Editor a el a -> Editor a el b -> Editor a el b #

(<*) :: Editor a el a -> Editor a el b -> Editor a el a #

liftElement :: UI el -> Editor a el () Source #

Lift an HTML element into a vacuous editor.

dimapE :: (a' -> a) -> (b -> b') -> Editor a el b -> Editor a' el b' Source #

applyE :: (el1 -> el2 -> el) -> Editor in_ el1 (a -> b) -> Editor in_ el2 a -> Editor in_ el b Source #

Editor composition

(|*|) :: Editor s Layout (b -> a) -> Editor s Layout b -> Editor s Layout a infixl 4 Source #

Left-right editor composition

(|*) :: Editor s Layout a -> UI Element -> Editor s Layout a infixl 5 Source #

Left-right composition of an element with a editor

(*|) :: UI Element -> Editor s Layout a -> Editor s Layout a infixl 5 Source #

Left-right composition of an element with a editor

(-*-) :: Editor s Layout (b -> a) -> Editor s Layout b -> Editor s Layout a infixl 4 Source #

Left-right editor composition

(-*) :: Editor s Layout a -> UI Element -> Editor s Layout a infixl 5 Source #

Left-right composition of an element with a editor

(*-) :: UI Element -> Editor s Layout a -> Editor s Layout a infixl 5 Source #

Left-right composition of an element with a editor

field :: Renderable m => String -> (out -> inn) -> Editor inn m a -> Editor out Layout a Source #

A helper that arranges a label and an editor horizontally.

fieldLayout :: (Renderable m, Renderable m') => (Layout -> m') -> String -> (out -> inn) -> Editor inn m a -> Editor out m' a Source #

A helper that arranges a label and an editor horizontally, wrapped in the given monoidal layout builder.

Editor constructors

editorSelection :: Ord a => Behavior [a] -> Behavior (a -> UI Element) -> Editor (Maybe a) (ListBox a) (Maybe a) Source #

An editor that presents a dynamic choice of values.

editorSum :: (Ord tag, Show tag, Renderable el) => (Layout -> Layout -> Layout) -> [(tag, Editor a el a)] -> (a -> tag) -> Editor a Layout a Source #

An editor for union types, built from editors for its constructors.

editorJust :: Editor (Maybe b) el (Maybe b) -> Editor b el b Source #

Ignores Nothing values and only updates for Just values