SybWidget-0.4.0: Library which aids constructing generic (SYB3-based) widgets

Graphics.UI.SybWidget.SybOuter

Contents

Description

Helper functions to creates generic widgets.

The parent type, which is refered thoughout the module documentation, could also be called the enclosing type. For example given:

data Foo = Foo Bar Boo

then the parent type of Bar and Boo will be Foo.

Synopsis

Documentation

class OuterWidget outer whereSource

Methods

updateLabel :: (PriLabel -> PriLabel) -> outer a -> outer aSource

data FullPart wid parent b Source

Widget with getter and setter.

Constructors

FullPart 

Fields

partWidget :: wid b
 
partGetter :: parent -> b

Extracts this parts value from the parent type

partSetter :: parent -> b -> parent

Sets this value on a parent type

mkGetterSetter :: forall ctx wid getM setM parent. (Monad getM, Monad setM, Data ctx parent) => Proxy ctx -> (forall a. wid a -> getM a) -> (forall a. wid a -> a -> setM ()) -> Spliter wid parent parent -> (getM parent, parent -> setM ())Source

Creates getter and setter command for a Spliter. That is, it will create two function which sets/gets all the parts of the Spliter.

mkFullSpliter :: forall ctx parent part. Data ctx parent => Proxy ctx -> Spliter part parent parent -> Spliter (FullPart part parent) parent parentSource

Creates a Spliter containing FullPart-s.

isSingleConstructor :: Data ctx a => Proxy ctx -> a -> BoolSource

Has this type exactly one constructor? This function is undefined for Int, Float, Double and Char.

mkSpliterSingleConstr :: forall ctx a outer. (Data ctx a, OuterWidget outer) => Proxy ctx -> (forall a1. Data ctx a1 => a1 -> outer a1) -> a -> Spliter outer a aSource

Constructs a Spliter using the constructor in the input type (y). If y has field labels, the individual parts are updated with the field label names.

Spliter

data Spliter part parent a Source

The Splitter type contains the splitting of a type into a Constructor and Parts.

The Spliter structure is reverse, in the sense that a type C a b c, where C is a constructor and a, b and c is values to the constructor, will be represented as (Splitter type in brackets):

(Part (part c) { C a b c } (Part (part b) { c -> C a b c } (Part (part a) { b -> c -> C a b c } (Constructor C)))) { a -> b -> c -> C a b c }

Constructors

Constructor a 
forall b . Typeable b => Part (part b) (Spliter part parent (b -> a)) 

mapParts :: forall partA partB parent. (forall q. Typeable q => partA q -> partB q) -> Spliter partA parent parent -> Spliter partB parent parentSource

Maps each part in a Spliter type.

mapPartsM :: forall partA partB parent m. Monad m => (forall q. Typeable q => partA q -> m (partB q)) -> Spliter partA parent parent -> m (Spliter partB parent parent)Source

Monadic version of mapParts. The mapping is done deep first. It is done deep first as we will then process the elements in the field order. E.g. if the spliter is based on the:

data Foo = Foo Int Double

then the Int will be processed first, then the Double.

mapPartsMDelay :: forall partA partB parent m. Monad m => (forall q. Typeable q => partA q -> Bool) -> (forall q. Typeable q => partA q -> m (partB q)) -> Spliter partA parent parent -> m (Spliter partB parent parent)Source

Like mapPartsM, except that processing of certain parts can be delayed. The first parameter decides which parts processing should be delayed.

This is usefull when fine grained control of execution order is desired.

spliterToListSource

Arguments

:: (forall c. Typeable c => part c -> abstractPart)

Function to transform each part in the spliter to a list element. Note that the parts have kind * -> *, but the output must be of kind *.

-> Spliter part a b 
-> [abstractPart] 

Transforms a spiltter to a list. The list will follow the constructor fields order.

zipSpliterWithList :: forall a m n part. (forall q. Typeable q => a -> part q -> part q) -> [a] -> Spliter part m n -> Spliter part m nSource

Zips a list with a spliter using f. The list members are zipped in the order of the constructor fields. If not enough list members are present the rest of the spilter is un-mapped.

Constructor-value map

mkConstrValMap :: (Data ctx a, RefMonad m ref) => Proxy ctx -> a -> m (ConstrValMap ref ctx a)Source

A map from from constructors to values. Used as memory when creating multi-constructor widgtes. This way each time the constructor is changed, we can look in the map to see if we had a privious value for the new constructor.

updateConstrValMap :: (Data ctx a, RefMonad m ref) => ConstrValMap ref ctx a -> a -> m ()Source

Updates the map with a new value.

lookupValue :: (Data ctx a, RefMonad m ref) => ConstrValMap ref ctx a -> Constr -> m (Maybe a)Source

Look in the map to see if we have a value for the constructor.

alwaysValue :: (Data ctx a, RefMonad m ref) => ConstrValMap ref ctx a -> Constr -> m aSource

Like lookupValue, except if it cannot find a value in the map one will be created using createInstance.

data ConstrValMap ref ctx a Source

Creating numeric widgets

numericGetSet :: (Data ctx a, RefMonad m ref) => Proxy ctx -> a -> m (String -> m a, a -> m String)Source

Returns a getter and setter command for numeric types. The getter and setter are applicable when numeric types are represented using String. The function uses sybRead and sybShow to parse and construct strings. In this way we avoid dependency on Show and Read type classes.

It is generally a good idea to avoid dependencies. And it can be essential to avoid dependency on Show and Read, if we want to implement generic widgets for functions, as we cannot define Show and Read for those.

It could be argued that Int, Double, Float, .. all are instances of Read and Show, and it therefore unneccesary to avoid using these classes. However, SYB will force any dependencies for these types on all types for which we want generic functionality. SYB does that as we make one piece of code handling all integer-like types, and one handling all real-numbered types. Thus, we only have access to the classes that are in the generic class's context.

The getter uses the last legitimate value when the input string is non-parseable.

sybRead :: Data ctx a => Proxy ctx -> a -> String -> Maybe aSource

Avoid dependency on the Read class, by using SYB to read a value. It has _only_ been tested for numeric types.

See also numericGetSet.

sybShow :: Data ctx a => Proxy ctx -> a -> StringSource

Avoid dependency on the Show class, by using SYB to show a value. It has _only_ been tested for numeric types.

See also numericGetSet.

Type label

typeLabel :: Data ctx a => Proxy ctx -> a -> PriLabelSource

Creates a default label for a type.