threepenny-editors-0.5.5: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors

Contents

Description

Types and combinators to create widgets for editing algebraic datatypes.

This module builds around the idea that editors usually have the same shape as the data they are editing. We can immediately take advantage of this to automatically build editors from datatype definitions.

data Person = Person { first, last, email :: String, age :: Int }

deriveGeneric ''Person

instance Editable Person

This produces a generic editor with a fixed vertical layout. To customize the layout, we can use a explicit instance and monoidal layout builders:

instance Editable Person where
  editor = Person <$> fieldLayout Next  "First:" first editor
                  <*> fieldLayout Break "Last:"  last  editor
                  <*> fieldLayout Next  "Email:" email editor
                  <*> fieldLayout Next  "Age:"   age   editor

We can take this a step further by repurposing datatype definitions to represent not only data, but also the collections of editors that are composed to build the datatype editor. This is done via the Purpose type and the Field type family.

data Person purpose =
  Person { first, last, email :: Field purpose String
         , age                :: Field purpose Int}

deriveGeneric ''Person

instance Editable (Person Data) where
  type EditorWidget (Person Data) = Person Edit
  editor = editorGenericBi

instance Renderable (Person Edit) where
  render = renderGeneric

renderGeneric will produce a vertical layout. A direct implementation would use standard threepenny layout combinators since the fields of Person Edit are instances of Widget:

instance Renderable (Person Edit) where
  render Person{..} =
    grid [[string "First:", element first, string "Email:", element email]
         ,[string "Last:",  element last, string "Age:", element age]
         ]

Synopsis

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

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 #

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

The class of Editable datatypes.

There are several ways to create an instance, from easiest to most advanced:

  • Automatically (via SOP), producing an editor with a vertical layout:
instance Editable MyDatatype
  • Using the applicative layout combinators:
 instance Editable MyDatatype where
   editor = MyDatatype <$> field "Name:" name editor
                       -*- field "Age:"  age  editor
  • Using a monoidal layout builder:
 instance Editable MyDatatype where
   editor = MyDatatype <$> fieldLayout Break "Name:" name editor
                       <*> fieldLayout Next  "Age:"  age  editor
  • Using a dual purpose datatype, leaving the layout details for the Renderable instance.
instance Editable (MyDatatype Data) where
  type EditorWidget (MyDatatype Data) = MyDatatype Edit
  editor = editorGenericBi

Associated Types

type EditorWidget a Source #

The widget type that realizes the editor. Defaults to Layout and only needs to be manually defined when using custom renderables.

Instances

Editable Bool Source # 

Associated Types

type EditorWidget Bool :: * Source #

Editable Double Source # 
Editable Int Source # 

Associated Types

type EditorWidget Int :: * Source #

Editable () Source # 

Associated Types

type EditorWidget () :: * Source #

Methods

editor :: Editor () (EditorWidget ()) () Source #

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

Associated Types

type EditorWidget [a] :: * Source #

Methods

editor :: Editor [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 :: Editor (a -*- b) (EditorWidget (a -*- b)) (a -*- b) Source #

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

Associated Types

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

Methods

editor :: Editor (a |*| b) (EditorWidget (a |*| b)) (a |*| b) Source #

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

Associated Types

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

Methods

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

dimapE :: (a' -> a) -> (b -> b') -> Editor a el b -> Editor a' 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.

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

Conceal the widget type of some Editor

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

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

A version of editor with a concealed widget type.

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

Conceal the widget type of some Editor

Dual purpose datatypes

type family Field (purpose :: Purpose) a where ... Source #

Type level fields. Used to define dual purpose datatypes, example:

data PersonF (purpose :: Purpose) = Person
  { education           :: Field purpose Education
  , firstName, lastName :: Field purpose String
  , age                 :: Field purpose (Maybe Int)
type Person = PersonF Data
type PersonEditor = PersonF Edit

Equations

Field Data a = a 
Field Edit a = EditorWidget a 

data Purpose Source #

Purpose is a kind for type level Fields

Constructors

Data 
Edit 

Generic editors

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

A generic editor derivation for SOP types.

The datatype arguments are layered in vertical fashion and labelled with field names if available.

editorGenericBi :: forall xs typ. (Generic (typ Data), Generic (typ Edit), All Editable xs, Code (typ Data) ~ '[xs], Code (typ Edit) ~ '[EditorWidgetsFor xs]) => Editor (typ Data) (typ Edit) (typ Data) Source #

A generic editor derivation for dual purpose datatypes with a single constructor.

e.g. for the datatype

 data Person purpose = Person { firstName, lastName :: Field purpose String }
 instance Editable (Person Data) where
     type EditorWidget (Person Data) = Person Edit
     editor = editorGenericBi

will be equivalent to

instance Editable (Person Data) where
 type EditorWidget (Person Data) = Person Edit
 editor = bipure DataItem DataItem
             <<*>> edit firstName editor
             <<*>> edit lastName editor

Widgets

data GenericWidget control a Source #

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 # 

Layouts

Monoidal layouts

newtype Vertical Source #

A monoidal layout builder that places everything in a single column

Constructors

Vertical 

Fields

newtype Horizontal Source #

A monoidal layout builder that places everything in a single row

Constructors

Horizontal 

data Columns Source #

A monoidal layout builder that lays elements in columns

Constructors

Next Layout

Continue in the same column

Break Layout

Continue in the next column

Custom layout definition

class Renderable w where Source #

Closely related to Widget, this class represents types that can be rendered to an Element, either directly or via Layout.

Minimal complete definition

render | getLayout

Methods

render :: w -> UI Element Source #

getLayout :: w -> Layout Source #

Instances

Renderable String Source # 
Renderable TextEntry Source # 
Renderable Element Source # 
Renderable Columns Source # 
Renderable Horizontal Source # 
Renderable Vertical Source # 
Renderable Layout Source # 
Renderable (ListBox a) Source # 
Renderable a => Renderable (UI a) Source # 

Methods

render :: UI a -> UI Element Source #

getLayout :: UI a -> Layout Source #

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

Methods

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

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

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

Methods

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

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

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

renderGeneric :: forall a xs. (Generic a, HasDatatypeInfo a, All Renderable xs, Code a ~ '[xs]) => a -> UI Element Source #

A generic render derivation for data types with a single constructor which renders the (labelled) fields in a vertical layout. For custom layouts use getLayoutGeneric.

e.g. given the declarations

data PersonEditor = PersonEditor { firstName, lastName :: EditorWidget String }
deriveGeneric ''PersonEditor

using renderGeneric to instantiate Renderable

instance Renderable PersonEditor where
  getLayout = renderGeneric

will be equivalent to writing the below by hand

instance Renderable PersonEditor where
  getLayout PersonEditor{..} =
      grid [ [string "First name:", element firstName]
           , [string "Last name:",  element lastName ]
           ]

getLayoutGeneric :: forall a xs. (Generic a, HasDatatypeInfo a, All Renderable xs, Code a ~ '[xs]) => a -> [[Layout]] Source #

A helper to implement getLayout for data types with a single constructor. Given a value, getLayoutGeneric returns a grid of Layouts with one row per field. Rows can carry one element, for unnamed fields; two elements, for named fields; or three elements, for operators.