| Safe Haskell | None |
|---|
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.
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).
- data CustomVar a
- class VarLength a where
- class VarLength a => CustomValue a where
- newVarC :: (Monad (m Preamble), ProcVarMonad m) => a -> m Preamble (CustomVar a)
- readVarC :: (Monad (m c), ProcVarMonad m) => CustomVar a -> m c a
- writeVarC :: (Monad (m c), ProcVarMonad m) => CustomVar a -> a -> m c ()
Documentation
Typeclass of values that can be stored in several
native variables (Var).
class VarLength a => CustomValue a whereSource
Typeclass of custom values, which can be stored in custom variables (CustomVar).
Methods
newVarC :: (Monad (m Preamble), ProcVarMonad m) => a -> m Preamble (CustomVar a)Source
Version of newVar for custom variables.
readVarC :: (Monad (m c), ProcVarMonad m) => CustomVar a -> m c aSource
Version of readVar for custom variables.
writeVarC :: (Monad (m c), ProcVarMonad m) => CustomVar a -> a -> m c ()Source
Version of writeVar for custom variables.
Instances
| CustomValue Proc_Text | |
| CustomValue Proc_Char | |
| CustomValue Proc_Image | |
| CustomValue Proc_Float | |
| CustomValue Proc_Int | |
| CustomValue Proc_Bool | |
| (CustomValue a, CustomValue b) => CustomValue (a, b) | |
| (CustomValue a, CustomValue b, CustomValue c) => CustomValue (a, b, c) |