threepenny-editors-0.5.6.1: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors.Layout

Contents

Description

A custom layout engine and combinators.

Synopsis

Renderableable widgets

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable TextEntry Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable Element Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable Columns Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable Horizontal Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable Vertical Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable Layout Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable (ListBox a) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Renderable a => Renderable (UI a) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

render :: UI a -> UI Element Source #

getLayout :: UI a -> Layout Source #

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

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

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

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

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

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

Renderable w => Renderable (EditorCollection k w) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Types

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

Defined in Graphics.UI.Threepenny.Editors.Types

Layout engine

data Layout Source #

A rathe limited, grid layout builder, probably not fit for general purpose use yet.

Constructors

Grid (Seq (Seq Layout))

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

Bundled Patterns

pattern Single :: UI Element -> Layout 

Layout monoids

Flat

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 

Columns

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

Type level layouts

data a |*| b Source #

Type level Horizontal layouts

Constructors

a :|*| b 
Instances
Bifoldable (|*|) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

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 #

Bifunctor (|*|) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

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

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

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

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

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

Generic (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Associated Types

type Code (a |*| b) :: [[*]] #

Methods

from :: (a |*| b) -> Rep (a |*| b) #

to :: Rep (a |*| b) -> a |*| b #

HasDatatypeInfo (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Associated Types

type DatatypeInfoOf (a |*| b) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (a |*| b) -> DatatypeInfo (Code (a |*| b)) #

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

emptyValue :: a |*| b Source #

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

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

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

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

Defined in Graphics.UI.Threepenny.Editors

Associated Types

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

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

Methods

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

listEditor :: Editor [a |*| b] (ListEditorWidget (a |*| b)) [a |*| b] Source #

type Code (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

type Code (a |*| b) = (a ': (b ': ([] :: [*]))) ': ([] :: [[*]])
type DatatypeInfoOf (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

type DatatypeInfoOf (a |*| b) = ADT "Graphics.UI.Threepenny.Editors.Layout" "|*|" (Infix ":|*|" LeftAssociative 9 ': ([] :: [ConstructorInfo]))
type EditorWidget (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors

type ListEditorWidget (a |*| b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors

data a -*- b Source #

Type level Vertical layouts

Constructors

a :-*- b 
Instances
Bifoldable (-*-) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

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 #

Bifunctor (-*-) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

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

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

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

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

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

Generic (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Associated Types

type Code (a -*- b) :: [[*]] #

Methods

from :: (a -*- b) -> Rep (a -*- b) #

to :: Rep (a -*- b) -> a -*- b #

HasDatatypeInfo (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

Associated Types

type DatatypeInfoOf (a -*- b) :: DatatypeInfo #

Methods

datatypeInfo :: proxy (a -*- b) -> DatatypeInfo (Code (a -*- b)) #

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

emptyValue :: a -*- b Source #

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

Defined in Graphics.UI.Threepenny.Editors.Layout

Methods

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

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

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

Defined in Graphics.UI.Threepenny.Editors

Associated Types

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

type ListEditorWidget (a -*- b) :: * Source #

Methods

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

listEditor :: Editor [a -*- b] (ListEditorWidget (a -*- b)) [a -*- b] Source #

type Code (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

type Code (a -*- b) = (a ': (b ': ([] :: [*]))) ': ([] :: [[*]])
type DatatypeInfoOf (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors.Layout

type DatatypeInfoOf (a -*- b) = ADT "Graphics.UI.Threepenny.Editors.Layout" "-*-" (Infix ":-*-" LeftAssociative 9 ': ([] :: [ConstructorInfo]))
type EditorWidget (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors

type ListEditorWidget (a -*- b) Source # 
Instance details

Defined in Graphics.UI.Threepenny.Editors