{-# Language ScopedTypeVariables #-}
module Csound.Typed.Control (
module Csound.Typed.GlobalState.SE,
module Csound.Typed.Control.Ref,
instr0, getIns, setDur,
freshId,
module Csound.Typed.Control.Mix,
module Csound.Typed.Control.Midi,
module Csound.Typed.Control.Api,
module Csound.Typed.Control.Osc,
module Csound.Typed.Control.Channel,
module Csound.Typed.Control.Sf2,
module Csound.Typed.Control.Evt,
module Csound.Typed.Control.Vco,
module Csound.Typed.Control.InstrRef,
module Csound.Typed.Control.ArrayTraverse,
module Csound.Typed.Control.MacrosArgs
) where
import Data.Proxy
import Csound.Typed.GlobalState.SE
import Csound.Typed.Control.Ref
import Csound.Typed.Control.Evt
import Csound.Typed.Control.Mix
import Csound.Typed.Control.Midi
import Csound.Typed.Control.Api
import Csound.Typed.Control.Osc
import Csound.Typed.Control.Channel
import Csound.Typed.Control.Sf2
import Csound.Typed.Control.Vco
import Csound.Typed.Control.InstrRef
import Csound.Typed.Control.ArrayTraverse
import Csound.Typed.Control.MacrosArgs
import Csound.Typed.Types
import Csound.Typed.GlobalState
instr0 :: forall a. Tuple a => SE a -> SE a
instr0 :: forall a. Tuple a => SE a -> SE a
instr0 SE a
a = a -> SE a
forall a. a -> SE a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> SE a) -> a -> SE a
forall a b. (a -> b) -> a -> b
$ GE [E] -> a
forall a. Tuple a => GE [E] -> a
toTuple (GE [E] -> a) -> GE [E] -> a
forall a b. (a -> b) -> a -> b
$ Int -> [Rate] -> SE [E] -> GE [E]
saveIns0 Int
ins0Arity (Proxy a -> [Rate]
forall a. Tuple a => Proxy a -> [Rate]
tupleRates (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) SE [E]
ins0Exp
where
ins0Exp :: SE [E]
ins0Exp = SE (GE [E]) -> SE [E]
forall a. SE (GE a) -> SE a
execGEinSE (SE (GE [E]) -> SE [E]) -> SE (GE [E]) -> SE [E]
forall a b. (a -> b) -> a -> b
$ (a -> GE [E]) -> SE a -> SE (GE [E])
forall a b. (a -> b) -> SE a -> SE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> GE [E]
forall a. Tuple a => a -> GE [E]
fromTuple SE a
a
ins0Arity :: Int
ins0Arity = Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a)
getIns :: forall a. Sigs a => SE a
getIns :: forall a. Sigs a => SE a
getIns = (GE [E] -> a) -> SE (GE [E]) -> SE a
forall a b. (a -> b) -> SE a -> SE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GE [E] -> a
forall a. Tuple a => GE [E] -> a
toTuple (SE (GE [E]) -> SE a) -> SE (GE [E]) -> SE a
forall a b. (a -> b) -> a -> b
$ Dep [E] -> SE (GE [E])
forall a. Dep a -> SE (GE a)
fromDep (Dep [E] -> SE (GE [E])) -> Dep [E] -> SE (GE [E])
forall a b. (a -> b) -> a -> b
$ Int -> Dep [E]
forall (m :: * -> *). Monad m => Int -> DepT m [E]
getIn (Proxy a -> Int
forall a. Tuple a => Proxy a -> Int
tupleArity (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a))
setDur :: Sigs a => D -> a -> a
setDur :: forall a. Sigs a => D -> a -> a
setDur D
mdt a
as = GE [E] -> a
forall a. Tuple a => GE [E] -> a
toTuple (GE [E] -> a) -> GE [E] -> a
forall a b. (a -> b) -> a -> b
$ do
E
dt <- D -> GE E
forall a. Val a => a -> GE E
toGE D
mdt
[E]
vals <- a -> GE [E]
forall a. Tuple a => a -> GE [E]
fromTuple a
as
E -> GE ()
setDurationForce E
dt
[E] -> GE [E]
forall a. a -> GE a
forall (m :: * -> *) a. Monad m => a -> m a
return [E]
vals
freshId :: SE D
freshId :: SE D
freshId = Dep D -> SE D
forall a. Dep a -> SE a
SE (Dep D -> SE D) -> Dep D -> SE D
forall a b. (a -> b) -> a -> b
$ (E -> D) -> DepT GE E -> Dep D
forall a b. (a -> b) -> DepT GE a -> DepT GE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap E -> D
forall a. Val a => E -> a
fromE DepT GE E
forall (m :: * -> *). Monad m => DepT m E
freeChn