threepenny-editors-0.2.0.14: Composable algebraic editors

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.Threepenny.Editors.Base

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 #

class Editable a where Source #

The class of Editable datatypes.

Minimal complete definition

editor

Methods

editor :: Behavior a -> Compose UI EditorDef a Source #

The editor factory

Editor definitions

data EditorDef a Source #

Instances

Functor EditorDef Source # 

Methods

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

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

Layouts

Editor composition

(|*|) :: Compose UI EditorDef (b -> a) -> Compose UI EditorDef b -> Compose UI EditorDef a infixl 4 Source #

Left-right editor composition

(|*) :: Compose UI EditorDef a -> UI Element -> Compose UI EditorDef a infixl 5 Source #

Left-right composition of an element with a editor

(*|) :: UI Element -> Compose UI EditorDef a -> Compose UI EditorDef a infixl 5 Source #

Left-right composition of an element with a editor

(-*-) :: Compose UI EditorDef (b -> a) -> Compose UI EditorDef b -> Compose UI EditorDef a infixl 4 Source #

Top-down editor composition

(-*) :: Compose UI EditorDef a -> UI Element -> Compose UI EditorDef a infixl 5 Source #

Top-down composition of an element with a editor

(*-) :: UI Element -> Compose UI EditorDef a -> Compose UI EditorDef a infixl 5 Source #

Top-down composition of an element with a editor

Editor constructors

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

An editor that presents a dynamic choice of values.

editorSum :: (Ord tag, Show tag) => [(tag, Compose UI EditorDef a)] -> (a -> tag) -> Behavior a -> Compose UI EditorDef a Source #

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

editorJust :: (Behavior (Maybe b) -> Compose UI EditorDef (Maybe b)) -> Behavior b -> Compose UI EditorDef b Source #

Ignores Nothing values and only updates for Just values

Reexports

newtype Compose k k1 f g a :: forall k k1. (k1 -> *) -> (k -> k1) -> k -> * infixr 9 #

Right-to-left composition of functors. The composition of applicative functors is always applicative, but the composition of monads is not always a monad.

Constructors

Compose infixr 9 

Fields

Instances

(Functor f, Functor g) => Functor (Compose * * f g) 

Methods

fmap :: (a -> b) -> Compose * * f g a -> Compose * * f g b #

(<$) :: a -> Compose * * f g b -> Compose * * f g a #

(Applicative f, Applicative g) => Applicative (Compose * * f g) 

Methods

pure :: a -> Compose * * f g a #

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b #

(*>) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g b #

(<*) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g a #

(Foldable f, Foldable g) => Foldable (Compose * * f g) 

Methods

fold :: Monoid m => Compose * * f g m -> m #

foldMap :: Monoid m => (a -> m) -> Compose * * f g a -> m #

foldr :: (a -> b -> b) -> b -> Compose * * f g a -> b #

foldr' :: (a -> b -> b) -> b -> Compose * * f g a -> b #

foldl :: (b -> a -> b) -> b -> Compose * * f g a -> b #

foldl' :: (b -> a -> b) -> b -> Compose * * f g a -> b #

foldr1 :: (a -> a -> a) -> Compose * * f g a -> a #

foldl1 :: (a -> a -> a) -> Compose * * f g a -> a #

toList :: Compose * * f g a -> [a] #

null :: Compose * * f g a -> Bool #

length :: Compose * * f g a -> Int #

elem :: Eq a => a -> Compose * * f g a -> Bool #

maximum :: Ord a => Compose * * f g a -> a #

minimum :: Ord a => Compose * * f g a -> a #

sum :: Num a => Compose * * f g a -> a #

product :: Num a => Compose * * f g a -> a #

(Traversable f, Traversable g) => Traversable (Compose * * f g) 

Methods

traverse :: Applicative f => (a -> f b) -> Compose * * f g a -> f (Compose * * f g b) #

sequenceA :: Applicative f => Compose * * f g (f a) -> f (Compose * * f g a) #

mapM :: Monad m => (a -> m b) -> Compose * * f g a -> m (Compose * * f g b) #

sequence :: Monad m => Compose * * f g (m a) -> m (Compose * * f g a) #

Functor f => Generic1 (Compose * * f g) 

Associated Types

type Rep1 (Compose * * f g :: * -> *) :: * -> * #

Methods

from1 :: Compose * * f g a -> Rep1 (Compose * * f g) a #

to1 :: Rep1 (Compose * * f g) a -> Compose * * f g a #

(Alternative f, Applicative g) => Alternative (Compose * * f g) 

Methods

empty :: Compose * * f g a #

(<|>) :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

some :: Compose * * f g a -> Compose * * f g [a] #

many :: Compose * * f g a -> Compose * * f g [a] #

(Eq1 f, Eq1 g) => Eq1 (Compose * * f g) 

Methods

liftEq :: (a -> b -> Bool) -> Compose * * f g a -> Compose * * f g b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (Compose * * f g) 

Methods

liftCompare :: (a -> b -> Ordering) -> Compose * * f g a -> Compose * * f g b -> Ordering #

(Read1 f, Read1 g) => Read1 (Compose * * f g) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Compose * * f g a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Compose * * f g a] #

(Show1 f, Show1 g) => Show1 (Compose * * f g) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Compose * * f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Compose * * f g a] -> ShowS #

(Eq1 f, Eq1 g, Eq a) => Eq (Compose * * f g a) 

Methods

(==) :: Compose * * f g a -> Compose * * f g a -> Bool #

(/=) :: Compose * * f g a -> Compose * * f g a -> Bool #

(Data (f (g a)), Typeable * k, Typeable * k1, Typeable (k1 -> k) g, Typeable (k -> *) f, Typeable k1 a) => Data (Compose k1 k f g a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall b. b -> c b) -> Compose k1 k f g a -> c (Compose k1 k f g a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Compose k1 k f g a) #

toConstr :: Compose k1 k f g a -> Constr #

dataTypeOf :: Compose k1 k f g a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Compose k1 k f g a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Compose k1 k f g a)) #

gmapT :: (forall b. Data b => b -> b) -> Compose k1 k f g a -> Compose k1 k f g a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compose k1 k f g a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compose k1 k f g a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Compose k1 k f g a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Compose k1 k f g a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Compose k1 k f g a -> m (Compose k1 k f g a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose k1 k f g a -> m (Compose k1 k f g a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Compose k1 k f g a -> m (Compose k1 k f g a) #

(Ord1 f, Ord1 g, Ord a) => Ord (Compose * * f g a) 

Methods

compare :: Compose * * f g a -> Compose * * f g a -> Ordering #

(<) :: Compose * * f g a -> Compose * * f g a -> Bool #

(<=) :: Compose * * f g a -> Compose * * f g a -> Bool #

(>) :: Compose * * f g a -> Compose * * f g a -> Bool #

(>=) :: Compose * * f g a -> Compose * * f g a -> Bool #

max :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

min :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

(Read1 f, Read1 g, Read a) => Read (Compose * * f g a) 

Methods

readsPrec :: Int -> ReadS (Compose * * f g a) #

readList :: ReadS [Compose * * f g a] #

readPrec :: ReadPrec (Compose * * f g a) #

readListPrec :: ReadPrec [Compose * * f g a] #

(Show1 f, Show1 g, Show a) => Show (Compose * * f g a) 

Methods

showsPrec :: Int -> Compose * * f g a -> ShowS #

show :: Compose * * f g a -> String #

showList :: [Compose * * f g a] -> ShowS #

Generic (Compose k1 k f g a) 

Associated Types

type Rep (Compose k1 k f g a) :: * -> * #

Methods

from :: Compose k1 k f g a -> Rep (Compose k1 k f g a) x #

to :: Rep (Compose k1 k f g a) x -> Compose k1 k f g a #

type Rep1 (Compose * * f g) 
type Rep1 (Compose * * f g) = D1 (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 (MetaCons "Compose" PrefixI True) (S1 (MetaSel (Just Symbol "getCompose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) f (Rec1 g))))
type Rep (Compose k1 k f g a) 
type Rep (Compose k1 k f g a) = D1 (MetaData "Compose" "Data.Functor.Compose" "base" True) (C1 (MetaCons "Compose" PrefixI True) (S1 (MetaSel (Just Symbol "getCompose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (g a)))))