threepenny-editors-0.4.1: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors

Contents

Synopsis

Editors

data Editor a Source #

A widget for editing values of type a.

Constructors

Editor 

Instances

Functor Editor Source # 

Methods

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

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

Widget (Editor a) Source # 

Methods

getElement :: Editor a -> Element #

data EditorFactory a b Source #

A function from Behavior a to Editor a

Instances

Profunctor EditorFactory Source # 

Methods

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

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

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

(#.) :: Coercible * c b => (b -> c) -> EditorFactory a b -> EditorFactory a c #

(.#) :: Coercible * b a => EditorFactory b c -> (a -> b) -> EditorFactory a c #

Functor (EditorFactory a) Source # 

Methods

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

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

createEditor :: EditorFactory b a -> Behavior b -> UI (Editor a) Source #

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

class Editable a where Source #

The class of Editable datatypes. . Define your own instance by using the Applicative composition operators or derive it via SOP.

Editor composition

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

Horizontal applicative composition.

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

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

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

Vertical applicative composition.

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

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

field :: String -> (out -> inn) -> EditorFactory inn a -> EditorFactory out a Source #

A helper that arranges a label with the field name and the editor horizontally.

newtype Vertically a b Source #

Applicative instance 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{..}

Constructors

Vertically 

Fields

Instances

Profunctor Vertically Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Vertically b c -> Vertically a d #

lmap :: (a -> b) -> Vertically b c -> Vertically a c #

rmap :: (b -> c) -> Vertically a b -> Vertically a c #

(#.) :: Coercible * c b => (b -> c) -> Vertically a b -> Vertically a c #

(.#) :: Coercible * b a => Vertically b c -> (a -> b) -> Vertically a c #

Functor (Vertically a) Source # 

Methods

fmap :: (a -> b) -> Vertically a a -> Vertically a b #

(<$) :: a -> Vertically a b -> Vertically a a #

Applicative (Vertically a) Source # 

Methods

pure :: a -> Vertically a a #

(<*>) :: Vertically a (a -> b) -> Vertically a a -> Vertically a b #

(*>) :: Vertically a a -> Vertically a b -> Vertically a b #

(<*) :: Vertically a a -> Vertically a b -> Vertically a a #

newtype Horizontally a b Source #

Applicative instance 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{..}

Constructors

Horizontally 

Instances

Profunctor Horizontally Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Horizontally b c -> Horizontally a d #

lmap :: (a -> b) -> Horizontally b c -> Horizontally a c #

rmap :: (b -> c) -> Horizontally a b -> Horizontally a c #

(#.) :: Coercible * c b => (b -> c) -> Horizontally a b -> Horizontally a c #

(.#) :: Coercible * b a => Horizontally b c -> (a -> b) -> Horizontally a c #

Functor (Horizontally a) Source # 

Methods

fmap :: (a -> b) -> Horizontally a a -> Horizontally a b #

(<$) :: a -> Horizontally a b -> Horizontally a a #

Applicative (Horizontally a) Source # 

Methods

pure :: a -> Horizontally a a #

(<*>) :: Horizontally a (a -> b) -> Horizontally a a -> Horizontally a b #

(*>) :: Horizontally a a -> Horizontally a b -> Horizontally a b #

(<*) :: Horizontally a a -> Horizontally a b -> Horizontally a a #

Editor constructors

editorReadShow :: (Read a, Show a) => EditorFactory (Maybe a) (Maybe a) Source #

An editor that presents a free form input.

editorEnumBounded :: (Show a, Ord a, Enum a, Bounded a) => Behavior (a -> UI Element) -> EditorFactory (Maybe a) (Maybe a) Source #

An editor that presents a choice of values.

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

An editor that presents a dynamic choice of values.

editorSum :: (Show tag, Ord tag) => (Layout -> Layout -> Layout) -> [(tag, EditorFactory b b)] -> (b -> tag) -> EditorFactory b b Source #

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

editorJust :: EditorFactory (Maybe a) (Maybe a) -> EditorFactory a a Source #

Ignores Nothing values and only updates for Just values

Generic editors

editorGeneric :: forall a. (Generic a, HasDatatypeInfo a, All (All Editable `And` All Default) (Code a)) => EditorFactory a a Source #

A generic editor for SOP types.

editorGenericSimple :: forall a xs. (Generic a, HasDatatypeInfo a, All Editable xs, Code a ~ '[xs]) => EditorFactory a a Source #

A generic editor for record types.

Layouts

newtype Layout Source #

Constructors

Grid (Seq (Seq (Maybe Element)))

A non empty list of rows, where all the rows are assumed to have the same length