threepenny-editors-0.5.0: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors.Types

Contents

Synopsis

Editors

data Editor editorElement a Source #

A widget for editing values of type a.

Constructors

Editor 

Fields

Instances

Bifunctor Editor Source # 

Methods

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

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

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

Functor (Editor editorElement) Source # 

Methods

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

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

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

Methods

getElement :: Editor el a -> Element #

edited :: Editor el a -> Event a Source #

editorElement :: Lens (Editor el a) (Editor el' a) el el' Source #

A lens over the editorElement field

newtype EditorFactory a el b Source #

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

Constructors

EF 

Fields

Instances

Bifunctor (EditorFactory a) Source # 

Methods

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

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

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

Biapplicative (EditorFactory a) Source # 

Methods

bipure :: a -> b -> EditorFactory a a b #

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

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

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

Functor (EditorFactory a el) Source # 

Methods

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

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

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

Methods

pure :: a -> EditorFactory a el a #

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

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

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

dimapEF :: (a' -> a) -> (b -> b') -> EditorFactory a el b -> EditorFactory a' el b' Source #

lmapEF :: (a' -> a) -> EditorFactory a el b -> EditorFactory a' el b Source #

Applies a function over the input

applyEF :: (el1 -> el2 -> el) -> EditorFactory in_ el1 (a -> b) -> EditorFactory in_ el2 a -> EditorFactory in_ el b Source #

createEditor :: Renderable w => EditorFactory a w b -> Behavior a -> UI (Editor Element b) Source #

Create an editor to display the argument. User edits are fed back via the edited Event.

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

A Setter over the element of the editor being built

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

A Setter over the input thing

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

A Setter over the output thing

Editor composition

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

Left-right editor composition

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

Left-right composition of an editorElement with a editor

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

Left-right composition of an editorElement with a editor

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

Left-right editor composition

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

Left-right composition of an editorElement with a editor

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

Left-right composition of an editorElement with a editor

field :: Renderable m => String -> (out -> inn) -> EditorFactory inn m a -> EditorFactory 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) -> EditorFactory inn m a -> EditorFactory 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) -> EditorFactory a el b -> EditorFactory a' el b Source #

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

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

pattern Horizontally :: forall a b. EditorFactory a Layout b -> EditorFactory 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. EditorFactory a Layout b -> EditorFactory 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

Editor constructors

editorSelection :: Ord a => Behavior [a] -> Behavior (a -> UI Element) -> EditorFactory (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, EditorFactory a el a)] -> (a -> tag) -> EditorFactory a Layout a Source #

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

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

Ignores Nothing values and only updates for Just values

Editor layout

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

Apply a layout builder.

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

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