threepenny-editors-0.5.6.1: 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 # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Types

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 # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Types

Methods

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

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

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

Defined in Graphics.UI.Threepenny.Editors.Types

Methods

getElement :: GenericWidget el a -> Element #

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

Defined in Graphics.UI.Threepenny.Editors.Types

widgetControl :: GenericWidget control a -> control Source #

The actual widget.

widgetTidings :: GenericWidget control a -> Tidings a Source #

The dynamic contents of the widget.

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

Bundled Patterns

pattern Horizontally :: Editor a Layout b -> Editor a Horizontal b

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 :: Editor a Layout b -> Editor a Vertical b

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

Instances
Bifunctor (Editor a) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Types

Methods

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

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

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

Biapplicative (Editor a) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Types

Methods

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

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

biliftA2 :: (a0 -> b -> c) -> (d -> e -> f) -> Editor a a0 d -> Editor a b e -> Editor a c f #

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

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

Functor (Editor a el) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Types

Methods

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

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

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

Defined in Graphics.UI.Threepenny.Editors.Types

Methods

pure :: a0 -> Editor a el a0 #

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

liftA2 :: (a0 -> b -> c) -> Editor a el a0 -> Editor a el b -> Editor a el c #

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

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

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

editorCollection :: forall k v w. (Ord k, Renderable w) => (Behavior (Maybe k, Map k v) -> EditorCollectionConfig k v) -> Editor v w v -> Editor (Maybe k, Map k v) (EditorCollection k w) (Maybe k, Map k v) Source #

A barebones editor for collections of editable items. Displays an index selector, add and delete buttons, and an editor for the selected item. Limitations: - Won't work with recursive data structures, due to the lack of FRP switch.

editorList :: (HasEmpty a, Renderable w) => Editor a w a -> Editor (Maybe Int, [a]) (EditorCollection Int w) (Maybe Int, [a]) Source #

A barebones editor for collections of editable items. Displays an index selector, add and delete buttons, and an editor for the selected item. Limitations: - Won't work with recursive data structures, due to the lack of FRP switch.

data EditorCollectionConfig k v Source #

Constructors

EditorCollectionConfig 

Fields

Representation of empty values

class HasEmpty a where Source #

This class defines how to represent empty values in a UI. A generic derivation is available for every SOP type.

Instances
HasEmpty Bool Source # 
Instance details

Defined in Data.HasEmpty

HasEmpty Char Source # 
Instance details

Defined in Data.HasEmpty

HasEmpty Double Source # 
Instance details

Defined in Data.HasEmpty

HasEmpty Int Source # 
Instance details

Defined in Data.HasEmpty

HasEmpty () Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: () Source #

HasEmpty Text Source # 
Instance details

Defined in Data.HasEmpty

HasEmpty [a] Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: [a] Source #

HasEmpty (Maybe a) Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: Maybe a Source #

HasEmpty a => HasEmpty (Identity a) Source # 
Instance details

Defined in Data.HasEmpty

HasEmpty (Seq k) Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: Seq k Source #

Ord k => HasEmpty (Set k) Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: Set k Source #

HasEmpty a => HasEmpty (I a) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors

Methods

emptyValue :: I a Source #

(HasEmpty a, HasEmpty b) => HasEmpty (a, b) Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: (a, b) Source #

Ord k => HasEmpty (Map k v) Source # 
Instance details

Defined in Data.HasEmpty

Methods

emptyValue :: Map k v Source #

(HasEmpty a, HasEmpty b) => HasEmpty (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

emptyValue :: a -*- b Source #

(HasEmpty a, HasEmpty b) => HasEmpty (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

emptyValue :: a |*| b Source #

All HasEmpty xs => HasEmpty (NP I xs) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors

Methods

emptyValue :: NP I xs Source #