threepenny-editors-0.5.1: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors

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

Editor factories

data 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.

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 #

someEditor :: Editable a => EditorFactory a Layout a Source #

A version of editor with a concealed widget type.

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.

class Renderable (EditorWidget a) => Editable a where Source #

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

Associated Types

type EditorWidget a Source #

Methods

editor :: EditorFactory a (EditorWidget a) a Source #

The editor factory

editor :: (Generic a, HasDatatypeInfo a, All (All Editable `And` All Default) (Code a), EditorWidget a ~ Layout) => EditorFactory a (EditorWidget a) a Source #

The editor factory

Instances

Editable Bool Source # 
Editable Double Source # 
Editable Int Source # 

Associated Types

type EditorWidget Int :: * Source #

Editable () Source # 

Associated Types

type EditorWidget () :: * Source #

(~) * a Char => Editable [a] Source # 

Associated Types

type EditorWidget [a] :: * Source #

Methods

editor :: EditorFactory [a] (EditorWidget [a]) [a] Source #

Editable (Maybe Double) Source # 
Editable (Maybe Int) Source # 

Associated Types

type EditorWidget (Maybe Int) :: * Source #

Editable a => Editable (Identity a) Source # 

Associated Types

type EditorWidget (Identity a) :: * Source #

(Editable a, Editable b) => Editable (a, b) Source # 

Associated Types

type EditorWidget (a, b) :: * Source #

Methods

editor :: EditorFactory (a, b) (EditorWidget (a, b)) (a, b) Source #

All * Editable xs => Editable (NP * I xs) Source #

Tuple editor without fields

Associated Types

type EditorWidget (NP * I xs) :: * Source #

Methods

editor :: EditorFactory (NP * I xs) (EditorWidget (NP * I xs)) (NP * I xs) Source #

data EditorWidgetFor a where Source #

A container for EditorWidget.

type family Field (usage :: Usage) a where ... Source #

Type level fields. Use this helper to define EditorWidget types. Example:

data PersonF (usage :: Usage) = Person
  { education           :: Field usage Education
  , firstName, lastName :: Field usage String
  , age                 :: Field usage (Maybe Int)
type Person = PersonF Value
type PersonEditor = PersonF Edit

Equations

Field Value a = a 
Field Edit a = EditorWidget a 

data Usage Source #

Usage is a kind for type level Fields

Constructors

Value 
Edit 

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.

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 layout

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

Apply a layout builder.

withSomeWidget :: Renderable w => EditorFactory a w b -> EditorFactory a Layout b Source #

Conceal the widget type of some Editor

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

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

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

Generic editors

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

A generic editor for SOP types.

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

A generic editor for record types.

Layouts

Monoidal layouts

newtype Vertical Source #

A layout monoid that places everything in a single column

Constructors

Vertical 

Fields

newtype Horizontal Source #

A layout monoid that places everything in a single row

Constructors

Horizontal 

data Columns Source #

A layout monoid that lays elements in columns

Constructors

Next Layout

Continue in the same column

Break Layout

Continue in the next column

Type level layouts

data a |*| b Source #

Type level Horizontal layouts

Constructors

a :|*| b 

Instances

Bifunctor (|*|) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> (a |*| c) -> b |*| d #

first :: (a -> b) -> (a |*| c) -> b |*| c #

second :: (b -> c) -> (a |*| b) -> a |*| c #

Biapplicative (|*|) Source # 

Methods

bipure :: a -> b -> a |*| b #

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

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

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

Bifoldable (|*|) Source # 

Methods

bifold :: Monoid m => (m |*| m) -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (a |*| b) -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (a |*| b) -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (a |*| b) -> c #

(Renderable a, Renderable b) => Renderable ((|*|) a b) Source # 

Methods

render :: (a |*| b) -> UI Element Source #

getLayout :: (a |*| b) -> Layout Source #

data a -*- b Source #

Type level Vertical layouts

Constructors

a :-*- b 

Instances

Bifunctor (-*-) Source # 

Methods

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

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

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

Biapplicative (-*-) Source # 

Methods

bipure :: a -> b -> a -*- b #

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

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

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

Bifoldable (-*-) Source # 

Methods

bifold :: Monoid m => (m -*- m) -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (a -*- b) -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (a -*- b) -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (a -*- b) -> c #

(Renderable a, Renderable b) => Renderable ((-*-) a b) Source # 

Methods

render :: (a -*- b) -> UI Element Source #

getLayout :: (a -*- b) -> Layout Source #

Layout manipulation

class Renderable w where Source #

Closely related to Widget, this class represents types that can be rendered to an Element

Methods

render :: w -> UI Element Source #

getLayout :: w -> Layout Source #

Orphan instances

(Applicative f, All * Default xs) => Default (NP * f xs) Source # 

Methods

def :: NP * f xs #