gooey-0.1.0.0: Graphical user interfaces that are renderable, change over time and eventually produce a value.

Copyright(c) 2015 Schell Scivally
LicenseMIT
MaintainerSchell Scivally <efsubenovex@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Control.GUI

Contents

Description

Graphical user interfaces that are renderable, change over time and eventually produce a value.

GUIs are comprised of event streams and renderable datatypes that change over time. A GUI is a monadic layer on top of automaton varying values provided by the varying library.

Synopsis

Definition

data UX a b Source

A discrete step in a "user experience". This is simply a type that discretely describes an eventual value on the right and a renderable datatype on the left. It is assumed that the left value is a datatype that represents a user inteface and that the user is interacting with it to eventually produce the datatype on the right.

Constructors

UX a (Event b) 

Instances

Functor (UX a) Source

A UX is a functor by applying a function to the contained event's value.

Methods

fmap :: (b -> c) -> UX a b -> UX a c

(<$) :: b -> UX a c -> UX a b

Monoid a => Applicative (UX a) Source

A UX is an applicative if its left datatype is a monoid. It replies to pure with an empty left value while the right value is the argument wrapped in an event. It means "the argument happens instantly with no user interface".

Methods

pure :: b -> UX a b

(<*>) :: UX a (b -> c) -> UX a b -> UX a c

(*>) :: UX a b -> UX a c -> UX a c

(<*) :: UX a b -> UX a c -> UX a b

Composite a m r t => Composite (UX a b) m r t Source

A UX is renderable if its left value is also renderable. It inherits all Renderable type variables from its left value and simply renders that value.

Methods

composite :: UX a b -> [(t, Element m r t)]

newtype GUI m i a b Source

A GUI is a UX that varies over some domain. What this means is that a graphical user interface is essentially a user experience that eventually produces a value. m is the underlying monad. i is the type of the user input. a is the renderable type - the interface itself. b is the eventual produced value.

Constructors

GUI 

Fields

Instances

(Monad m, Monoid a) => Monad (GUI m i a) Source

A GUI is a monad if its UX's left value is a monoid. It responds to >>= by returning a new GUI that runs until it produces a value, then that value is used to create yet another GUI.

Methods

(>>=) :: GUI m i a b -> (b -> GUI m i a c) -> GUI m i a c

(>>) :: GUI m i a b -> GUI m i a c -> GUI m i a c

return :: b -> GUI m i a b

fail :: String -> GUI m i a b

Monad m => Functor (GUI m i a) Source

A GUI is a functor by applying a function to the eventual produced value.

Methods

fmap :: (b -> c) -> GUI m i a b -> GUI m i a c

(<$) :: b -> GUI m i a c -> GUI m i a b

(Monad m, Monoid a) => Applicative (GUI m i a) Source

A GUI is applicative if its UX's left value is a monoid. It responds to pure by returning a GUI that has no user interface and immediately produces the argument. It responds to <*> by applying the left argument to the right. Each side's left UX value will be mappend 'd.

Methods

pure :: b -> GUI m i a b

(<*>) :: GUI m i a (b -> c) -> GUI m i a b -> GUI m i a c

(*>) :: GUI m i a b -> GUI m i a c -> GUI m i a c

(<*) :: GUI m i a b -> GUI m i a c -> GUI m i a b

(MonadIO m, Monoid a) => MonadIO (GUI m i a) Source

A GUI can perform IO if its underlying monad can perform IO.

Methods

liftIO :: IO b -> GUI m i a b

(Monad m, Monoid a, Monoid b) => Monoid (GUI m i a b) Source

A GUI can be a monoid if its UX's left and right types are monoids. The identity is a GUI that has no user interface and immediately produces an event who's value is the identity of its UX's right type. The associative operation is to combine the two GUIs with combineGUI.

Methods

mempty :: GUI m i a b

mappend :: GUI m i a b -> GUI m i a b -> GUI m i a b

mconcat :: [GUI m i a b] -> GUI m i a b

Creation

In order to create a GUI you must first have a datatype that is Renderable. Then you must create a varying value of that datatype. Also needed is an event stream that eventually ends the user's interaction. The idea is that your interface varies over time and/or user input but eventually produces a result value that can be used in a monadic sequence.

gui Source

Arguments

:: (Monad m, Composite a m r t) 
=> Var m i a

The stream of a changing user interface.

-> Var m i (Event b)

The event stream that concludes a user's interaction. When this stream produces an event the interaction will end and the merging function will be used to create the GUI's return type.

-> (a -> b -> c)

The merging function that combines the interface's final value with the value produced by the event stream.

-> GUI m i [(t, Element m r t)] c 

Creates a new GUI displaying an interface that eventually produces a value. The type used to represent the user interface must have a Decomposable instance, that way the resulting GUI's discrete values can be rendered.

Transformation

Simply put - here we are applying some kind of transformation to your renderable interface. This most likely a standard two or three dimensional affine transformation. Since the transformation also changes over the same domain it's possible to tween GUIs.

transformGUI :: (Monad m, Monoid t) => Var m i t -> GUI m i [(t, d)] b -> GUI m i [(t, d)] b Source

Transforms a GUI. transformGUI :: (Monad m, Monoid t, Composite a m r t) => Var m i t -- ^ The stream of a changing transformation. -> GUI m i a b -- ^ The GUI to transform. -> GUI m i a b

Combination

Combining two GUIs creates a new GUI.

combineGUI Source

Arguments

:: (Monad m, Monoid u) 
=> GUI m i u a

The first GUI.

-> GUI m i u b

The second GUI.

-> (a -> b -> c)

The merging function.

-> GUI m i u c 

Combines two GUIs. The resulting GUI will not produce a value until both component GUIs have produced a value. At that moment a merging function is used to combine the two values into the resulting GUI's return type. The component GUIs' graphical representations (the left UX values) are mappendd together.