module Csound.Typed.Opcode.SerialIO (
    
    
    
    serialBegin, serialEnd, serialFlush, serialPrint, serialRead, serialWrite, serialWrite_i) where

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

-- 

-- | 
-- Open a serial port.
--
-- Open a serial port for arduino.
--
-- > iPort  serialBegin  SPortName [, ibaudRate]
--
-- csound doc: <http://csound.com/docs/manual/serialBegin.html>
serialBegin ::  Str -> SE D
serialBegin :: Str -> SE D
serialBegin Str
b1 = (E -> D) -> SE E -> SE D
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ( GE E -> D
D (GE E -> D) -> (E -> GE E) -> E -> D
forall b c a. (b -> c) -> (a -> b) -> a -> c
. E -> GE E
forall (m :: * -> *) a. Monad m => a -> m a
return) (SE E -> SE D) -> SE E -> SE D
forall a b. (a -> b) -> a -> b
$ Dep E -> SE E
forall a. Dep a -> SE a
SE (Dep E -> SE E) -> Dep E -> SE E
forall a b. (a -> b) -> a -> b
$ (E -> Dep E
forall (m :: * -> *). Monad m => E -> DepT m E
depT (E -> Dep E) -> Dep E -> Dep E
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Dep E -> Dep E) -> Dep E -> Dep E
forall a b. (a -> b) -> a -> b
$ GE E -> Dep E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> Dep E) -> GE E -> Dep 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
<$> Str -> GE E
unStr Str
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"serialBegin" [(Rate
Ir,[Rate
Sr,Rate
Ir])] [E
a1]

-- | 
-- Close a serial port.
--
-- Close a serial port for arduino.
--
-- >   serialEnd  iPort
--
-- csound doc: <http://csound.com/docs/manual/serialEnd.html>
serialEnd ::  D -> SE ()
serialEnd :: D -> SE ()
serialEnd 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 ()) -> Dep E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Dep E -> Dep ()) -> Dep E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> Dep E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> Dep E) -> GE E -> Dep 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
"serialEnd" [(Rate
Xr,[Rate
Ir])] [E
a1]

-- | 
-- Flush data from a serial port.
--
-- Flush to the screen any bytes (up to 32k) in the input buffer.  
-- Note that these bytes will be cleared from the buffer.
-- use this opcode mainly for debugging messages.
-- If you want to mix debugging and other communication 
-- messages over the same port, you will need to manually
-- parse the data with the serialRead opcode.
--
-- >   serialFlush  iPort
--
-- csound doc: <http://csound.com/docs/manual/serialFlush.html>
serialFlush ::  D -> SE ()
serialFlush :: D -> SE ()
serialFlush 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 ()) -> Dep E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Dep E -> Dep ()) -> Dep E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> Dep E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> Dep E) -> GE E -> Dep 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
"serialFlush" [(Rate
Xr,[Rate
Ir])] [E
a1]

-- | 
-- Print data from a serial port.
--
-- Print to the screen any bytes (up to 32k) in the input buffer.  
-- Note that these bytes will be cleared from the buffer.
-- use this opcode mainly for debugging messages.
-- If you want to mix debugging and other communication 
-- messages over the same port, you will need to manually
-- parse the data with the serialRead opcode.
--
-- >   serialPrint  iPort
--
-- csound doc: <http://csound.com/docs/manual/serialPrint.html>
serialPrint ::  D -> SE ()
serialPrint :: D -> SE ()
serialPrint 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 ()) -> Dep E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Dep E -> Dep ()) -> Dep E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> Dep E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> Dep E) -> GE E -> Dep 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
"serialPrint" [(Rate
Xr,[Rate
Ir])] [E
a1]

-- | 
-- Read data from a serial port.
--
-- Read data from a serial port for arduino.
--
-- > kByte  serialRead  iPort
--
-- csound doc: <http://csound.com/docs/manual/serialRead.html>
serialRead ::  D -> Sig
serialRead :: D -> Sig
serialRead D
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
<$> D -> GE E
unD D
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"serialRead" [(Rate
Kr,[Rate
Ir])] [E
a1]

-- | 
-- Write data to a serial port.
--
-- Write data to a serial port for arduino.
--
-- >   serialWrite  iPort, iByte
-- >   serialWrite  iPort, kByte
-- >   serialWrite  iPort, SBytes
--
-- csound doc: <http://csound.com/docs/manual/serialWrite.html>
serialWrite ::  D -> D -> SE ()
serialWrite :: D -> D -> SE ()
serialWrite D
b1 D
b2 = 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 ()) -> Dep E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Dep E -> Dep ()) -> Dep E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> Dep E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> Dep E) -> GE E -> Dep E
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
<*> D -> GE E
unD D
b2
    where f :: E -> E -> E
f E
a1 E
a2 = Name -> Spec1 -> [E] -> E
opcs Name
"serialWrite" [(Rate
Xr,[Rate
Ir,Rate
Ir])] [E
a1,E
a2]

-- | 
-- Write data to a serial port.
--
-- Write data to a serial port for arduino.
--
-- >   serialWrite_i  iPort, iByte
-- >   serialWrite_i  iPort, SBytes
--
-- csound doc: <http://csound.com/docs/manual/serialWrite_i.html>
serialWrite_i ::  D -> D -> SE ()
serialWrite_i :: D -> D -> SE ()
serialWrite_i D
b1 D
b2 = 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 ()) -> Dep E -> Dep ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<) (Dep E -> Dep ()) -> Dep E -> Dep ()
forall a b. (a -> b) -> a -> b
$ GE E -> Dep E
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (GE E -> Dep E) -> GE E -> Dep E
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
<*> D -> GE E
unD D
b2
    where f :: E -> E -> E
f E
a1 E
a2 = Name -> Spec1 -> [E] -> E
opcs Name
"serialWrite_i" [(Rate
Xr,[Rate
Ir,Rate
Ir])] [E
a1,E
a2]