hommage-0.0.5: Haskell Offline Music Manipulation And Generation EDSLSource codeContentsIndex
Sound.Hommage.Parameter
Contents
Field
Hetero List
Description
This module contains a datatype Field and sone type classes. It is used to construct record-like datatypes.
Synopsis
data Field c a = Field {
getField :: c -> a
setField :: (a -> a) -> c -> c
}
(<>) :: Field a b -> Field c a -> Field c b
fstField :: Field (a, b) a
sndField :: Field (a, b) b
data UpdateField c
= forall a . (Field c a) := a
| forall a . (Field c a) :$ (a -> a)
| If (CheckField c) [UpdateField c] [UpdateField c]
data CheckField c
= forall a . (Field c a) :? (a -> Bool)
| And [CheckField c]
| Or [CheckField c]
updateField :: UpdateField c -> c -> c
checkField :: CheckField c -> c -> Bool
applyField :: [UpdateField c] -> c -> c
withField :: [UpdateField a] -> (a -> b) -> a -> b
data Group c a = Group {
isGroup :: c -> Maybe a
mkGroup :: a -> c
}
leftGroup :: Group (Either a b) a
rightGroup :: Group (Either a b) b
(><) :: Group a b -> Group c a -> Group c b
data LM a b m = (m a) :>> (b m)
data NilM m = NilM
class PushFields m where
pushFields :: m (Field c) -> m (Field (x, c))
class ToFields a r where
toFields :: a -> r (Field a)
class PushGroups m where
pushGroups :: m (Group c) -> m (Group (Either x c))
class ToGroups a r where
toGroups :: a -> r (Group a)
Documentation

Example:

To create a "record" with the accessors/modificators first you have to define the type of the record, It must be a right-associative list of pairs, just like a LISP list. The rightmost element must be () . The following Example defines a record with information for music generation.

 type DefaultNote = (Int, (Double, (Char, ())))     

Then a default value should be defined.

 defaultNote = (0, (1.0, ('a' , ())))
 defaultNote :: DefaultNote 

For each "datafield" the Field must be declared.

 pitch :: Field DefaultNote Int 
 volume :: Field DefaultNote Double 
 channel :: Field DefaultNote Char 

Creating the fields is done with toField applied to a value of the "record" type.

 pitch :>> volume :>> channel :>> NilM = toFields defaultNote 

Is is recommended to declare all types and match all results of toFields incl. the NilM at the end.

NOTE:

 pitch :>> volume :>> channel :>> NilM = toFields (undefined :: DefaultNote)

should work too.

Field
data Field c a Source
A Field record field is an interface to access a type field which is part of a type record . A Field is used to access and modify subtypes ("datafields") of a record-like datastructure. In this module, a right-associative pair structure is taken as record-type with "datafields" in the fst parts of the pairs.
Constructors
Field
getField :: c -> a
setField :: (a -> a) -> c -> c
(<>) :: Field a b -> Field c a -> Field c bSource
fstField :: Field (a, b) aSource
sndField :: Field (a, b) bSource
data UpdateField c Source
Constructors
forall a . (Field c a) := a
forall a . (Field c a) :$ (a -> a)
If (CheckField c) [UpdateField c] [UpdateField c]
data CheckField c Source
Constructors
forall a . (Field c a) :? (a -> Bool)
And [CheckField c]
Or [CheckField c]
updateField :: UpdateField c -> c -> cSource
checkField :: CheckField c -> c -> BoolSource
applyField :: [UpdateField c] -> c -> cSource
withField :: [UpdateField a] -> (a -> b) -> a -> bSource
data Group c a Source
Constructors
Group
isGroup :: c -> Maybe a
mkGroup :: a -> c
leftGroup :: Group (Either a b) aSource
rightGroup :: Group (Either a b) bSource
(><) :: Group a b -> Group c a -> Group c bSource
Hetero List
data LM a b m Source
Constructors
(m a) :>> (b m)
show/hide Instances
PushGroups b => PushGroups (LM a b)
PushFields b => PushFields (LM a b)
(ToGroups b b', PushGroups b') => ToGroups (Either a b) (LM a b')
(PushFields b', ToFields b b') => ToFields ((,) a b) (LM a b')
data NilM m Source
The correct type is: data NilM (m :: * -> *) = NilM . (But Haddock rejects this definition. GHC will need it) data NilM m = NilM
Constructors
NilM
show/hide Instances
class PushFields m whereSource
Methods
pushFields :: m (Field c) -> m (Field (x, c))Source
show/hide Instances
class ToFields a r whereSource
Methods
toFields :: a -> r (Field a)Source
show/hide Instances
ToFields () NilM
ToFields () NilM
(PushFields b', ToFields b b') => ToFields ((,) a b) (LM a b')
(PushFields b', ToFields b b') => ToFields ((,) a b) (LM a b')
class PushGroups m whereSource
Methods
pushGroups :: m (Group c) -> m (Group (Either x c))Source
show/hide Instances
class ToGroups a r whereSource
Methods
toGroups :: a -> r (Group a)Source
show/hide Instances
ToGroups () NilM
ToGroups () NilM
(ToGroups b b', PushGroups b') => ToGroups (Either a b) (LM a b')
(ToGroups b b', PushGroups b') => ToGroups (Either a b) (LM a b')
Produced by Haddock version 2.4.2