module Sound.Sc3.Ugen.Primitive where
import Sound.Sc3.Common.Rate
import Sound.Sc3.Ugen.Brackets
data UgenId = NoId | Uid Int deriving (Eq UgenId
Eq UgenId =>
(UgenId -> UgenId -> Ordering)
-> (UgenId -> UgenId -> Bool)
-> (UgenId -> UgenId -> Bool)
-> (UgenId -> UgenId -> Bool)
-> (UgenId -> UgenId -> Bool)
-> (UgenId -> UgenId -> UgenId)
-> (UgenId -> UgenId -> UgenId)
-> Ord UgenId
UgenId -> UgenId -> Bool
UgenId -> UgenId -> Ordering
UgenId -> UgenId -> UgenId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UgenId -> UgenId -> Ordering
compare :: UgenId -> UgenId -> Ordering
$c< :: UgenId -> UgenId -> Bool
< :: UgenId -> UgenId -> Bool
$c<= :: UgenId -> UgenId -> Bool
<= :: UgenId -> UgenId -> Bool
$c> :: UgenId -> UgenId -> Bool
> :: UgenId -> UgenId -> Bool
$c>= :: UgenId -> UgenId -> Bool
>= :: UgenId -> UgenId -> Bool
$cmax :: UgenId -> UgenId -> UgenId
max :: UgenId -> UgenId -> UgenId
$cmin :: UgenId -> UgenId -> UgenId
min :: UgenId -> UgenId -> UgenId
Ord, UgenId -> UgenId -> Bool
(UgenId -> UgenId -> Bool)
-> (UgenId -> UgenId -> Bool) -> Eq UgenId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UgenId -> UgenId -> Bool
== :: UgenId -> UgenId -> Bool
$c/= :: UgenId -> UgenId -> Bool
/= :: UgenId -> UgenId -> Bool
Eq, ReadPrec [UgenId]
ReadPrec UgenId
Int -> ReadS UgenId
ReadS [UgenId]
(Int -> ReadS UgenId)
-> ReadS [UgenId]
-> ReadPrec UgenId
-> ReadPrec [UgenId]
-> Read UgenId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UgenId
readsPrec :: Int -> ReadS UgenId
$creadList :: ReadS [UgenId]
readList :: ReadS [UgenId]
$creadPrec :: ReadPrec UgenId
readPrec :: ReadPrec UgenId
$creadListPrec :: ReadPrec [UgenId]
readListPrec :: ReadPrec [UgenId]
Read, Int -> UgenId -> ShowS
[UgenId] -> ShowS
UgenId -> String
(Int -> UgenId -> ShowS)
-> (UgenId -> String) -> ([UgenId] -> ShowS) -> Show UgenId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UgenId -> ShowS
showsPrec :: Int -> UgenId -> ShowS
$cshow :: UgenId -> String
show :: UgenId -> String
$cshowList :: [UgenId] -> ShowS
showList :: [UgenId] -> ShowS
Show)
no_id :: UgenId
no_id :: UgenId
no_id = UgenId
NoId
type Output = Rate
newtype Special = Special Int
deriving (Eq Special
Eq Special =>
(Special -> Special -> Ordering)
-> (Special -> Special -> Bool)
-> (Special -> Special -> Bool)
-> (Special -> Special -> Bool)
-> (Special -> Special -> Bool)
-> (Special -> Special -> Special)
-> (Special -> Special -> Special)
-> Ord Special
Special -> Special -> Bool
Special -> Special -> Ordering
Special -> Special -> Special
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Special -> Special -> Ordering
compare :: Special -> Special -> Ordering
$c< :: Special -> Special -> Bool
< :: Special -> Special -> Bool
$c<= :: Special -> Special -> Bool
<= :: Special -> Special -> Bool
$c> :: Special -> Special -> Bool
> :: Special -> Special -> Bool
$c>= :: Special -> Special -> Bool
>= :: Special -> Special -> Bool
$cmax :: Special -> Special -> Special
max :: Special -> Special -> Special
$cmin :: Special -> Special -> Special
min :: Special -> Special -> Special
Ord, Special -> Special -> Bool
(Special -> Special -> Bool)
-> (Special -> Special -> Bool) -> Eq Special
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Special -> Special -> Bool
== :: Special -> Special -> Bool
$c/= :: Special -> Special -> Bool
/= :: Special -> Special -> Bool
Eq, ReadPrec [Special]
ReadPrec Special
Int -> ReadS Special
ReadS [Special]
(Int -> ReadS Special)
-> ReadS [Special]
-> ReadPrec Special
-> ReadPrec [Special]
-> Read Special
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Special
readsPrec :: Int -> ReadS Special
$creadList :: ReadS [Special]
readList :: ReadS [Special]
$creadPrec :: ReadPrec Special
readPrec :: ReadPrec Special
$creadListPrec :: ReadPrec [Special]
readListPrec :: ReadPrec [Special]
Read, Int -> Special -> ShowS
[Special] -> ShowS
Special -> String
(Int -> Special -> ShowS)
-> (Special -> String) -> ([Special] -> ShowS) -> Show Special
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Special -> ShowS
showsPrec :: Int -> Special -> ShowS
$cshow :: Special -> String
show :: Special -> String
$cshowList :: [Special] -> ShowS
showList :: [Special] -> ShowS
Show)
data Primitive t = Primitive
{ forall t. Primitive t -> Rate
ugenRate :: Rate
, forall t. Primitive t -> String
ugenName :: String
, forall t. Primitive t -> [t]
ugenInputs :: [t]
, forall t. Primitive t -> [Rate]
ugenOutputs :: [Output]
, forall t. Primitive t -> Special
ugenSpecial :: Special
, forall t. Primitive t -> UgenId
ugenId :: UgenId
, forall t. Primitive t -> Brackets
primitiveBrackets :: Brackets
}
deriving (Eq (Primitive t)
Eq (Primitive t) =>
(Primitive t -> Primitive t -> Ordering)
-> (Primitive t -> Primitive t -> Bool)
-> (Primitive t -> Primitive t -> Bool)
-> (Primitive t -> Primitive t -> Bool)
-> (Primitive t -> Primitive t -> Bool)
-> (Primitive t -> Primitive t -> Primitive t)
-> (Primitive t -> Primitive t -> Primitive t)
-> Ord (Primitive t)
Primitive t -> Primitive t -> Bool
Primitive t -> Primitive t -> Ordering
Primitive t -> Primitive t -> Primitive t
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall t. Ord t => Eq (Primitive t)
forall t. Ord t => Primitive t -> Primitive t -> Bool
forall t. Ord t => Primitive t -> Primitive t -> Ordering
forall t. Ord t => Primitive t -> Primitive t -> Primitive t
$ccompare :: forall t. Ord t => Primitive t -> Primitive t -> Ordering
compare :: Primitive t -> Primitive t -> Ordering
$c< :: forall t. Ord t => Primitive t -> Primitive t -> Bool
< :: Primitive t -> Primitive t -> Bool
$c<= :: forall t. Ord t => Primitive t -> Primitive t -> Bool
<= :: Primitive t -> Primitive t -> Bool
$c> :: forall t. Ord t => Primitive t -> Primitive t -> Bool
> :: Primitive t -> Primitive t -> Bool
$c>= :: forall t. Ord t => Primitive t -> Primitive t -> Bool
>= :: Primitive t -> Primitive t -> Bool
$cmax :: forall t. Ord t => Primitive t -> Primitive t -> Primitive t
max :: Primitive t -> Primitive t -> Primitive t
$cmin :: forall t. Ord t => Primitive t -> Primitive t -> Primitive t
min :: Primitive t -> Primitive t -> Primitive t
Ord, Primitive t -> Primitive t -> Bool
(Primitive t -> Primitive t -> Bool)
-> (Primitive t -> Primitive t -> Bool) -> Eq (Primitive t)
forall t. Eq t => Primitive t -> Primitive t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall t. Eq t => Primitive t -> Primitive t -> Bool
== :: Primitive t -> Primitive t -> Bool
$c/= :: forall t. Eq t => Primitive t -> Primitive t -> Bool
/= :: Primitive t -> Primitive t -> Bool
Eq, ReadPrec [Primitive t]
ReadPrec (Primitive t)
Int -> ReadS (Primitive t)
ReadS [Primitive t]
(Int -> ReadS (Primitive t))
-> ReadS [Primitive t]
-> ReadPrec (Primitive t)
-> ReadPrec [Primitive t]
-> Read (Primitive t)
forall t. Read t => ReadPrec [Primitive t]
forall t. Read t => ReadPrec (Primitive t)
forall t. Read t => Int -> ReadS (Primitive t)
forall t. Read t => ReadS [Primitive t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall t. Read t => Int -> ReadS (Primitive t)
readsPrec :: Int -> ReadS (Primitive t)
$creadList :: forall t. Read t => ReadS [Primitive t]
readList :: ReadS [Primitive t]
$creadPrec :: forall t. Read t => ReadPrec (Primitive t)
readPrec :: ReadPrec (Primitive t)
$creadListPrec :: forall t. Read t => ReadPrec [Primitive t]
readListPrec :: ReadPrec [Primitive t]
Read, Int -> Primitive t -> ShowS
[Primitive t] -> ShowS
Primitive t -> String
(Int -> Primitive t -> ShowS)
-> (Primitive t -> String)
-> ([Primitive t] -> ShowS)
-> Show (Primitive t)
forall t. Show t => Int -> Primitive t -> ShowS
forall t. Show t => [Primitive t] -> ShowS
forall t. Show t => Primitive t -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall t. Show t => Int -> Primitive t -> ShowS
showsPrec :: Int -> Primitive t -> ShowS
$cshow :: forall t. Show t => Primitive t -> String
show :: Primitive t -> String
$cshowList :: forall t. Show t => [Primitive t] -> ShowS
showList :: [Primitive t] -> ShowS
Show)