hsc3-0.17: Haskell SuperCollider

Safe HaskellSafe
LanguageHaskell98

Sound.SC3.Common.UId

Contents

Description

Unique identifier types and classes. Used by non-deterministic (noise) and non-sharable (demand) unit generators.

Synopsis

Id & UId

type Id = Int Source #

Identifiers are integers.

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.

Methods

generateUId :: m Int Source #

Instances
UId IO Source # 
Instance details

Defined in Sound.SC3.Common.UId

UId (StateT Int Identity) Source #

Requires FlexibleInstances.

Instance details

Defined in Sound.SC3.Common.UId

UId m => UId (ReaderT t m) Source # 
Instance details

Defined in Sound.SC3.Common.UId

UId_ST

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], Int) Source #

Thread state through sequence of runState.

uid_st_seq_ :: [UId_ST t] -> [t] Source #

fst of uid_st_seq.

uid_st_seq_ (replicate 3 generateUId) == [0,1,2]

Lift

liftUId1 :: UId m => (Int -> Fn1 a b) -> Fn1 a (m b) Source #

Unary UId lift.

liftUId2 :: UId m => (Int -> Fn2 a b c) -> Fn2 a b (m c) Source #

Binary UId lift.

liftUId3 :: UId m => (Int -> Fn3 a b c d) -> Fn3 a b c (m d) Source #

Ternary UId lift.

liftUId4 :: UId m => (Int -> Fn4 a b c d e) -> Fn4 a b c d (m e) Source #

Quaternary UId lift.

ID

class Hashable32 a => ID a where Source #

Typeclass to constrain UGen identifiers.

map resolveID [0::Int,1] == [3151710696,1500603050]
map resolveID ['α','β'] == [1439603815,4131151318]
map resolveID [('α','β'),('β','α')] == [3538183581,3750624898]
map resolveID [('α',('α','β')),('β',('α','β'))] == [0020082907,2688286317]

Minimal complete definition

Nothing

Methods

resolveID :: a -> Id Source #

Instances
ID Char Source # 
Instance details

Defined in Sound.SC3.Common.UId

Methods

resolveID :: Char -> Id Source #

ID Int Source # 
Instance details

Defined in Sound.SC3.Common.UId

Methods

resolveID :: Int -> Id Source #

(ID p, ID q) => ID (p, q) Source # 
Instance details

Defined in Sound.SC3.Common.UId

Methods

resolveID :: (p, q) -> Id Source #

id_seq :: ID a => Int -> a -> [Id] Source #

n identifiers from x.

id_seq 10 'α' == [945 .. 954]