module Csound.Typed.Opcode.Miscellaneous (
    
    
    
    directory, fareylen, fareyleni, modmatrix, pwd, select, system_i, system, tableshuffle, tableshufflei) where

import Control.Monad.Trans.Class
import Csound.Dynamic
import Csound.Typed

-- 

-- | 
-- Reads a directory and outputs to a string array a list of file names.
--
-- Reads a directory for files and passes them to a string array. Users can set the file type by passing a file extension as a string.
--
-- > SFiles[]  directory  SDirectory[, SExtention]
--
-- csound doc: <http://csound.com/docs/manual/directory.html>
directory ::  Str -> Str
directory :: Str -> Str
directory Str
b1 = GE E -> Str
Str (GE E -> Str) -> GE E -> Str
forall a b. (a -> b) -> a -> b
$ E -> E
f (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Str -> GE E
unStr Str
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"directory" [(Rate
Sr,[Rate
Sr,Rate
Sr])] [E
a1]

-- | 
-- returns the length of a Farey Sequence.
--
-- This opcode can be used in conjunction with GENfarey.
-- It calculates the length of Farey Sequence Fn. Its length is given by:
-- |Fn| = 1 + SUM over n phi(m) 
-- where phi(m) is Euler's totient function, which gives the number of integers ≤ m that are coprime to m.
--
-- > kfl  fareylen  kfn
--
-- csound doc: <http://csound.com/docs/manual/fareylen.html>
fareylen ::  Tab -> Sig
fareylen :: Tab -> Sig
fareylen Tab
b1 = GE E -> Sig
Sig (GE E -> Sig) -> GE E -> Sig
forall a b. (a -> b) -> a -> b
$ E -> E
f (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tab -> GE E
unTab Tab
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"fareylen" [(Rate
Kr,[Rate
Kr])] [E
a1]

-- | 
-- returns the length of a Farey Sequence.
--
-- This opcode can be used in conjunction with GENfarey.
-- It calculates the length of Farey Sequence Fn. Its length is given by:
-- |Fn| = 1 + SUM over n phi(m) 
-- where phi(m) is Euler's totient function, which gives the number of integers ≤ m that are coprime to m.
--
-- > ifl  fareyleni  ifn
--
-- csound doc: <http://csound.com/docs/manual/fareyleni.html>
fareyleni ::  Tab -> D
fareyleni :: Tab -> D
fareyleni Tab
b1 = GE E -> D
D (GE E -> D) -> GE E -> D
forall a b. (a -> b) -> a -> b
$ E -> E
f (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tab -> GE E
unTab Tab
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"fareyleni" [(Rate
Ir,[Rate
Ir])] [E
a1]

-- | 
-- Modulation matrix opcode with optimizations for sparse matrices.
--
-- The opcode can be used to let a large number of k-rate modulator
--       variables modulate a large number of k-rate parameter variables,
--       with arbitrary scaling of each modulator-to-parameter
--       connection.  Csound ftables are used to hold both the input
--       (parameter)  variables, the modulator variables, and the scaling
--       coefficients. Output variables are written to another Csound ftable.
--
-- >  modmatrix  iresfn, isrcmodfn, isrcparmfn, imodscale, inum_mod, \\
-- >     inum_parm, kupdate
--
-- csound doc: <http://csound.com/docs/manual/modmatrix.html>
modmatrix ::  Tab -> Tab -> Tab -> D -> D -> D -> Sig -> SE ()
modmatrix :: Tab -> Tab -> Tab -> D -> D -> D -> Sig -> SE ()
modmatrix Tab
b1 Tab
b2 Tab
b3 D
b4 D
b5 D
b6 Sig
b7 = Dep () -> SE ()
forall a. Dep a -> SE a
SE (Dep () -> SE ()) -> Dep () -> SE ()
forall a b. (a -> b) -> a -> b
$ (E -> Dep ()
forall (m :: * -> *). Monad m => E -> DepT m ()
depT_ (E -> Dep ()) -> DepT GE E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (DepT GE E -> Dep ()) -> DepT GE E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> DepT GE E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> DepT GE E) -> GE E -> DepT GE E
forall a b. (a -> b) -> a -> b
$ E -> E -> E -> E -> E -> E -> E -> E
f (E -> E -> E -> E -> E -> E -> E -> E)
-> GE E -> GE (E -> E -> E -> E -> E -> E -> E)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Tab -> GE E
unTab Tab
b1 GE (E -> E -> E -> E -> E -> E -> E)
-> GE E -> GE (E -> E -> E -> E -> E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Tab -> GE E
unTab Tab
b2 GE (E -> E -> E -> E -> E -> E)
-> GE E -> GE (E -> E -> E -> E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Tab -> GE E
unTab Tab
b3 GE (E -> E -> E -> E -> E) -> GE E -> GE (E -> E -> E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> D -> GE E
unD D
b4 GE (E -> E -> E -> E) -> GE E -> GE (E -> E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> D -> GE E
unD D
b5 GE (E -> E -> E) -> GE E -> GE (E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> D -> GE E
unD D
b6 GE (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b7
    where f :: E -> E -> E -> E -> E -> E -> E -> E
f E
a1 E
a2 E
a3 E
a4 E
a5 E
a6 E
a7 = Name -> Spec1 -> [E] -> E
opcs Name
"modmatrix" [(Rate
Xr,[Rate
Ir,Rate
Ir,Rate
Ir,Rate
Ir,Rate
Ir,Rate
Ir,Rate
Kr])] [E
a1
                                                                                  ,E
a2
                                                                                  ,E
a3
                                                                                  ,E
a4
                                                                                  ,E
a5
                                                                                  ,E
a6
                                                                                  ,E
a7]

-- | 
-- Asks the underlying operating system for the current directory
--       name as a string.
--
-- pwd call the operating system to determine
--       the current directory (folder).  pwd runs
--       at i-time only.
--
-- > Sres  pwd 
--
-- csound doc: <http://csound.com/docs/manual/pwd.html>
pwd ::   Str
pwd :: Str
pwd  = GE E -> Str
Str (GE E -> Str) -> GE E -> Str
forall a b. (a -> b) -> a -> b
$ E -> GE E
forall (m :: * -> *) a. Monad m => a -> m a
return (E -> GE E) -> E -> GE E
forall a b. (a -> b) -> a -> b
$ E
f 
    where f :: E
f  = Name -> Spec1 -> [E] -> E
opcs Name
"pwd" [(Rate
Sr,[])] []

-- | 
-- Select sample value based on audio-rate comparisons.
--
-- Select sample value from three based on audio-rate comparisons of
--       two signals.
--
-- > aout  select  a1, a2, aless, aequal, amore
--
-- csound doc: <http://csound.com/docs/manual/select.html>
select ::  Sig -> Sig -> Sig -> Sig -> Sig -> Sig
select :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
select Sig
b1 Sig
b2 Sig
b3 Sig
b4 Sig
b5 = GE E -> Sig
Sig (GE E -> Sig) -> GE E -> Sig
forall a b. (a -> b) -> a -> b
$ E -> E -> E -> E -> E -> E
f (E -> E -> E -> E -> E -> E) -> GE E -> GE (E -> E -> E -> E -> E)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Sig -> GE E
unSig Sig
b1 GE (E -> E -> E -> E -> E) -> GE E -> GE (E -> E -> E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b2 GE (E -> E -> E -> E) -> GE E -> GE (E -> E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b3 GE (E -> E -> E) -> GE E -> GE (E -> E)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b4 GE (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b5
    where f :: E -> E -> E -> E -> E -> E
f E
a1 E
a2 E
a3 E
a4 E
a5 = Name -> Spec1 -> [E] -> E
opcs Name
"select" [(Rate
Ar,[Rate
Ar,Rate
Ar,Rate
Ar,Rate
Ar,Rate
Ar])] [E
a1,E
a2,E
a3,E
a4,E
a5]

-- | 
-- Call an external program via the system call
--
-- system and system_i call
--     any external command understood by the operating system, similarly
--     to the C function     system(). system_i runs
--     at i-time only, while 
--       system runs both at initialization and
--       performance time.
--
-- > ires  system_i  itrig, Scmd, [inowait]
--
-- csound doc: <http://csound.com/docs/manual/system.html>
system_i ::  D -> Str -> D
system_i :: D -> Str -> D
system_i D
b1 Str
b2 = GE E -> D
D (GE E -> D) -> GE E -> D
forall a b. (a -> b) -> a -> b
$ E -> E -> E
f (E -> E -> E) -> GE E -> GE (E -> E)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> D -> GE E
unD D
b1 GE (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Str -> GE E
unStr Str
b2
    where f :: E -> E -> E
f E
a1 E
a2 = Name -> Spec1 -> [E] -> E
opcs Name
"system_i" [(Rate
Ir,[Rate
Ir,Rate
Sr,Rate
Ir])] [E
a1,E
a2]

-- | 
-- Call an external program via the system call
--
-- system and system_i call
--     any external command understood by the operating system, similarly
--     to the C function     system(). system_i runs
--     at i-time only, while 
--       system runs both at initialization and
--       performance time.
--
-- > kres  system  ktrig, Scmd, [knowait]
--
-- csound doc: <http://csound.com/docs/manual/system.html>
system ::  Sig -> Str -> Sig
system :: Sig -> Str -> Sig
system Sig
b1 Str
b2 = GE E -> Sig
Sig (GE E -> Sig) -> GE E -> Sig
forall a b. (a -> b) -> a -> b
$ E -> E -> E
f (E -> E -> E) -> GE E -> GE (E -> E)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Sig -> GE E
unSig Sig
b1 GE (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Str -> GE E
unStr Str
b2
    where f :: E -> E -> E
f E
a1 E
a2 = Name -> Spec1 -> [E] -> E
opcs Name
"system" [(Rate
Kr,[Rate
Kr,Rate
Sr,Rate
Kr])] [E
a1,E
a2]

-- | 
-- shuffles the content of a function table so that each element of the source
--       table is put into a different random position.
--
-- This opcode can be used in order to shuffle the content of
--       function tables into a random order but without loosing any of
--       the elements. Imagine shuffling a deck of cards. Each element of
--       the table is copied to a different random position. If that
--       position was already chosen before then the next free position
--       is chosen. The length of the table remains the same.
--
-- >  tableshuffle  ktablenum
--
-- csound doc: <http://csound.com/docs/manual/tableshuffle.html>
tableshuffle ::  Sig -> SE ()
tableshuffle :: Sig -> SE ()
tableshuffle Sig
b1 = Dep () -> SE ()
forall a. Dep a -> SE a
SE (Dep () -> SE ()) -> Dep () -> SE ()
forall a b. (a -> b) -> a -> b
$ (E -> Dep ()
forall (m :: * -> *). Monad m => E -> DepT m ()
depT_ (E -> Dep ()) -> DepT GE E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (DepT GE E -> Dep ()) -> DepT GE E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> DepT GE E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> DepT GE E) -> GE E -> DepT GE E
forall a b. (a -> b) -> a -> b
$ E -> E
f (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Sig -> GE E
unSig Sig
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"tableshuffle" [(Rate
Xr,[Rate
Kr])] [E
a1]

-- | 
-- shuffles the content of a function table so that each element of the source
--       table is put into a different random position.
--
-- This opcode can be used in order to shuffle the content of
--       function tables into a random order but without loosing any of
--       the elements. Imagine shuffling a deck of cards. Each element of
--       the table is copied to a different random position. If that
--       position was already chosen before then the next free position
--       is chosen. The length of the table remains the same.
--
-- >  tableshufflei  itablenum
--
-- csound doc: <http://csound.com/docs/manual/tableshuffle.html>
tableshufflei ::  D -> SE ()
tableshufflei :: D -> SE ()
tableshufflei D
b1 = Dep () -> SE ()
forall a. Dep a -> SE a
SE (Dep () -> SE ()) -> Dep () -> SE ()
forall a b. (a -> b) -> a -> b
$ (E -> Dep ()
forall (m :: * -> *). Monad m => E -> DepT m ()
depT_ (E -> Dep ()) -> DepT GE E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (DepT GE E -> Dep ()) -> DepT GE E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> DepT GE E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> DepT GE E) -> GE E -> DepT GE E
forall a b. (a -> b) -> a -> b
$ E -> E
f (E -> E) -> GE E -> GE E
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> D -> GE E
unD D
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"tableshufflei" [(Rate
Xr,[Rate
Ir])] [E
a1]