Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Unique identifier types and classes. Used by non-deterministic (noise) and non-sharable (demand) unit generators.
Synopsis
- type Id = Int
- class (Functor m, Applicative m, Monad m) => Uid m where
- generateUid :: m Int
- type Uid_St = State Int
- uid_id_eval :: Identity t -> t
- uid_st_eval :: Uid_St t -> t
- uid_st_seq :: [Uid_St t] -> ([t], Int)
- uid_st_seq_ :: [Uid_St t] -> [t]
- liftUid1 :: Uid m => (Int -> Fn1 a b) -> Fn1 a (m b)
- liftUid2 :: Uid m => (Int -> Fn2 a b c) -> Fn2 a b (m c)
- liftUid3 :: Uid m => (Int -> Fn3 a b c d) -> Fn3 a b c (m d)
- liftUid4 :: Uid m => (Int -> Fn4 a b c d e) -> Fn4 a b c d (m e)
- liftUid5 :: Uid m => (Int -> Fn5 a b c d e f) -> Fn5 a b c d e (m f)
- liftUid6 :: Uid m => (Int -> Fn6 a b c d e f g) -> Fn6 a b c d e f (m g)
- liftUid10 :: Uid m => (Int -> Fn10 a b c d e f g h i j k) -> Fn10 a b c d e f g h i j (m k)
- liftUid11 :: Uid m => (Int -> Fn11 a b c d e f g h i j k l) -> Fn11 a b c d e f g h i j k (m l)
- class Hashable32 a => ID a where
- id_seq :: ID a => Int -> a -> [Id]
Id & Uid
class (Functor m, Applicative m, Monad m) => Uid m where Source #
A class indicating a monad (and functor and applicative) that will generate a sequence of unique integer identifiers.
generateUid :: m Int Source #
Uid_St
uid_id_eval :: Identity t -> t Source #
Alias for runIdentity
.
uid_st_eval :: Uid_St t -> t Source #
evalState
with initial state of zero.
uid_st_eval (replicateM 3 generateUid) == [0, 1, 2]
uid_st_seq_ :: [Uid_St t] -> [t] Source #
fst
of uid_st_seq
.
uid_st_seq_ (replicate 3 generateUid) == [0, 1, 2]
Lift
liftUid6 :: Uid m => (Int -> Fn6 a b c d e f g) -> Fn6 a b c d e f (m g) Source #
6-parameter Uid lift.
liftUid10 :: Uid m => (Int -> Fn10 a b c d e f g h i j k) -> Fn10 a b c d e f g h i j (m k) Source #
10-parameter Uid lift.
liftUid11 :: Uid m => (Int -> Fn11 a b c d e f g h i j k l) -> Fn11 a b c d e f g h i j k (m l) Source #
11-parameter Uid lift.
ID
class Hashable32 a => ID a where Source #
Typeclass to constrain Ugen identifiers. Char inputs are hashed to generate longer seeds for when ir (constant) random Ugens are optimised.
map resolveID [0::Int,1] == [0, 1] map resolveID ['α', 'β'] == [1439603815, 4131151318] map resolveID [('α', 'β'),('β', 'α')] == [3538183581, 3750624898] map resolveID [('α',('α', 'β')),('β',('α', 'β'))] == [0020082907, 2688286317] map resolveID [('α', 'α', 'β'),('β', 'α', 'β')] == [0020082907, 2688286317]
Nothing