processing-1.2.0.1: Web graphic applications with processing.js.

Safe HaskellNone

Graphics.Web.Processing.Mid.CustomVar

Description

This module implements variables which may contain values from types different from the native types (Proc_* types).

To make a type available to custom variables, it needs to be instantiated in the CustomValue class, which is subclass of the VarLength class. These instances are derivables using the DeriveGeneric extension. Things you need are: enable the DeriveGeneric language extension, import GHC.Generics, derive a Generic instance of your type and then write the following instances (where Foo is any type of interest):

 instance VarLength Foo
 instance CustomValue Foo

Note that Foo must be made from other types that are instances of CustomValue. Also, note that instances of VarLength or CustomValue can not be recursive or sum types. An example:

 {-# LANGUAGE DeriveGeneric #-}

 import Graphics.Web.Processing.Mid
 import Graphics.Web.Processing.Mid.CustomVar
 import GHC.Generics

 data Point = Point Proc_Float Proc_Float
                deriving Generic

 instance VarLength Point
 instance CustomValue Point

Types instance of the CustomValue class can be contained by a special type of variables, called CustomVar (Custom Variable). Functions for custom variables are equal to the function for regular variables, except that they all end in C. For example, newVar is called newVarC for custom variables.

There are also arrays which may contain custom values. See CustomArrayVar.

The dependency of this module in several language extensions was the reason to make it separate from the rest of the mid interface where it belongs to. Somehow, it forces the user to use DeriveGeneric and import GHC.Generics to do something useful with it (more than use custom variables for tuples).

Synopsis

Documentation

data CustomVar a Source

Variable with custom values.

Instances

data CustomArrayVar a Source

Array variable of custom values.

customArraySize :: CustomArrayVar a -> IntSource

Size of the custom array.

class VarLength a whereSource

Typeclass of values that can be stored in several native variables (Var).

Methods

varLength :: a -> IntSource

Calculate how many native variables are needed to store a value.

class VarLength a => CustomValue a whereSource

Typeclass of custom values, which can be stored in custom variables (CustomVar).

Methods

newVarC :: (Monad (m Preamble), ProcMonad m) => a -> m Preamble (CustomVar a)Source

Version of newVar for custom variables.

newArrayVarC :: (Monad (m Preamble), ProcMonad m) => [a] -> m Preamble (CustomArrayVar a)Source

Version of newArrayVar for custom variables.

readVarC :: (Monad (m c), ProcMonad m) => CustomVar a -> m c aSource

Version of readVar for custom variables.

writeVarC :: (Monad (m c), ProcMonad m) => CustomVar a -> a -> m c ()Source

Version of writeVar for custom variables.

ifC :: Proc_Bool -> a -> a -> aSource

Version of if_ for custom values.

readArrayVarC :: (ProcMonad m, Monad (m c), CustomValue a) => CustomArrayVar a -> Proc_Int -> m c aSource

Read a component of a custom array variable.

writeArrayVarC :: (ProcMonad m, Monad (m c), CustomValue a) => CustomArrayVar a -> Proc_Int -> a -> m c ()Source

Write a component of a custom array variable.