threepenny-editors-0.5.2: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors.Types

Contents

Synopsis

GenericWidgets

data GenericWidget control a Source #

A widget for editing values of type a.

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 # 

widgetControl :: forall control a control. Lens (GenericWidget control a) (GenericWidget control a) control control Source #

widgetTidings :: forall control a a. Lens (GenericWidget control a) (GenericWidget control a) (Tidings a) (Tidings a) Source #

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

Lift an HTML element into a vacuous editor.

newtype Editor a el b Source #

A function from Behavior a to GenericWidget b All the three type arguments are functorial, but a is contravariant. Editor is a Biapplicative functor on el and b, and a Profunctor on a and b.

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 #

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

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

Applies a function over the input

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

editorFactoryElement :: Setter (Editor a el b) (Editor a el' b) el el' Source #

A Setter over the element of the editor being built

editorFactoryInput :: Setter (Editor a el b) (Editor a' el b) a' a Source #

A Setter over the input thing

editorFactoryOutput :: Setter (Editor a el b) (Editor a el b') b b' Source #

A Setter over the output thing

GenericWidget 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 with the field name and the 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 with the field name and the editor horizontally. This version takes a Layout builder as well.

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

Focus the editor on the field retrieved by the getter. Use when composing editors via the Biapplicative interface

personEditor :: Editor Person PersonEditor Person
personEditor =
    bipure Person Person
      <<*>> edit education editor
      <<*>> edit firstName editor
      <<*>> edit lastName  editor

pattern Horizontally :: forall a b. Editor a Layout b -> Editor a Horizontal b Source #

Applicative modifier for horizontal composition of editor factories. This can be used in conjunction with ApplicativeDo as:

editorPerson = horizontally $ do
      firstName <- Horizontally $ field "First:" firstName editor
      lastName  <- Horizontally $ field "Last:"  lastName editor
      age       <- Horizontally $ field "Age:"   age editor
      return Person{..}

DEPRECATED: Use the Horizontal layout builder instead

pattern Vertically :: forall a b. Editor a Layout b -> Editor a Vertical b Source #

Applicative modifier for vertical composition of editor factories. This can be used in conjunction with ApplicativeDo as:

editorPerson = vertically $ do
      firstName <- Vertically $ field "First:" firstName editor
      lastName  <- Vertically $ field "Last:"  lastName editor
      age       <- Vertically $ field "Age:"   age editor
      return Person{..}

DEPRECATED: Use the Vertical layout builder instead

GenericWidget 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

GenericWidget layout

withLayout :: (layout -> layout') -> Editor a layout b -> Editor a layout' b Source #

Apply a layout builder.

construct :: Renderable m => Editor a m b -> Editor a Layout b Source #

Construct a concrete Layout. Useful when combining heterogeneours layout builders.