module Csound.Typed.Opcode.ImageProcessingOpcodes (
    
    
    
    imagecreate, imagefree, imagegetpixel, imageload, imagesave, imagesetpixel, imagesize) where

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

-- 

-- | 
-- Create an empty image of a given size.
--
-- Create an empty image of a given size. Individual pixel values can then be set with. imagegetpixel.
--
-- > iimagenum  imagecreate  iwidth, iheight
--
-- csound doc: <http://csound.com/docs/manual/imagecreate.html>
imagecreate ::  D -> D -> SE D
imagecreate :: D -> D -> SE D
imagecreate D
b1 D
b2 = (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 -> 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
"imagecreate" [(Rate
Ir,[Rate
Ir,Rate
Ir])] [E
a1,E
a2]

-- | 
-- Frees memory allocated for a previously loaded or created image.
--
-- >  imagefree  iimagenum
--
-- csound doc: <http://csound.com/docs/manual/imagefree.html>
imagefree ::  D -> SE ()
imagefree :: D -> SE ()
imagefree 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
"imagefree" [(Rate
Xr,[Rate
Ir])] [E
a1]

-- | 
-- Return the RGB pixel values of a previously opened or created image.
--
-- Return the RGB pixel values of a previously opened or created image. An image can be loaded with imageload. An empty image can be created with imagecreate.
--
-- > ared, agreen, ablue  imagegetpixel  iimagenum, ax, ay
-- > kred, kgreen, kblue  imagegetpixel  iimagenum, kx, ky
--
-- csound doc: <http://csound.com/docs/manual/imagegetpixel.html>
imagegetpixel ::  D -> Sig -> Sig -> (Sig,Sig,Sig)
imagegetpixel :: D -> Sig -> Sig -> (Sig, Sig, Sig)
imagegetpixel D
b1 Sig
b2 Sig
b3 = GE (MultiOut [E]) -> (Sig, Sig, Sig)
forall a. Tuple a => GE (MultiOut [E]) -> a
pureTuple (GE (MultiOut [E]) -> (Sig, Sig, Sig))
-> GE (MultiOut [E]) -> (Sig, Sig, Sig)
forall a b. (a -> b) -> a -> b
$ E -> E -> E -> MultiOut [E]
f (E -> E -> E -> MultiOut [E])
-> GE E -> GE (E -> E -> MultiOut [E])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> D -> GE E
unD D
b1 GE (E -> E -> MultiOut [E]) -> GE E -> GE (E -> MultiOut [E])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b2 GE (E -> MultiOut [E]) -> GE E -> GE (MultiOut [E])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Sig -> GE E
unSig Sig
b3
    where f :: E -> E -> E -> MultiOut [E]
f E
a1 E
a2 E
a3 = Name -> Specs -> [E] -> MultiOut [E]
mopcs Name
"imagegetpixel" ([Rate
Kr,Rate
Kr,Rate
Kr],[Rate
Ir,Rate
Kr,Rate
Kr]) [E
a1,E
a2,E
a3]

-- | 
-- Load an image.
--
-- Load an image and return a reference to it. Individual pixel values can then be accessed with imagegetpixel.
--
-- > iimagenum  imageload  filename
--
-- csound doc: <http://csound.com/docs/manual/imageload.html>
imageload ::  Spec -> SE D
imageload :: Spec -> SE D
imageload Spec
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
<$> Spec -> GE E
unSpec Spec
b1
    where f :: E -> E
f E
a1 = Name -> Spec1 -> [E] -> E
opcs Name
"imageload" [(Rate
Ir,[Rate
Fr])] [E
a1]

-- | 
-- Save a previously created image.
--
-- Save a previously created image. An empty image can be created with imagecreate and its pixel RGB values can be set with imagesetpixel. The image will be saved in PNG format.
--
-- >  imagesave  iimagenum, filename
--
-- csound doc: <http://csound.com/docs/manual/imagesave.html>
imagesave ::  D -> Spec -> SE ()
imagesave :: D -> Spec -> SE ()
imagesave D
b1 Spec
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
<*> Spec -> GE E
unSpec Spec
b2
    where f :: E -> E -> E
f E
a1 E
a2 = Name -> Spec1 -> [E] -> E
opcs Name
"imagesave" [(Rate
Xr,[Rate
Ir,Rate
Fr])] [E
a1,E
a2]

-- | 
-- Set the RGB value of a pixel inside a previously opened or created image.
--
-- Set the RGB value of a pixel inside a previously opened or created image. An image can be loaded with imageload. An empty image can be created with imagecreate and saved with imagesave.
--
-- >  imagesetpixel  iimagenum, ax, ay, ared, agreen, ablue
-- >  imagesetpixel  iimagenum, kx, ky, kred, kgreen, kblue
--
-- csound doc: <http://csound.com/docs/manual/imagesetpixel.html>
imagesetpixel ::  D -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
imagesetpixel :: D -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
imagesetpixel D
b1 Sig
b2 Sig
b3 Sig
b4 Sig
b5 Sig
b6 = 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 -> E -> E -> E -> E
f (E -> E -> E -> E -> E -> E -> E)
-> GE E -> GE (E -> E -> E -> E -> E -> E)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> D -> GE E
unD D
b1 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
<*> Sig -> GE E
unSig Sig
b2 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
b3 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
b4 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
b5 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
b6
    where f :: E -> E -> E -> E -> E -> E -> E
f E
a1 E
a2 E
a3 E
a4 E
a5 E
a6 = Name -> Spec1 -> [E] -> E
opcs Name
"imagesetpixel" [(Rate
Xr,[Rate
Ir,Rate
Ar,Rate
Ar,Rate
Ar,Rate
Ar,Rate
Ar])] [E
a1,E
a2,E
a3,E
a4,E
a5,E
a6]

-- | 
-- Return the width and height of a previously opened or created image.
--
-- Return the width and height of a previously opened or created image. An image can be loaded with imageload. An empty image can be created with imagecreate.
--
-- > iwidth, iheight  imagesize  iimagenum
--
-- csound doc: <http://csound.com/docs/manual/imagesize.html>
imagesize ::  D -> (D,D)
imagesize :: D -> (D, D)
imagesize D
b1 = GE (MultiOut [E]) -> (D, D)
forall a. Tuple a => GE (MultiOut [E]) -> a
pureTuple (GE (MultiOut [E]) -> (D, D)) -> GE (MultiOut [E]) -> (D, D)
forall a b. (a -> b) -> a -> b
$ E -> MultiOut [E]
f (E -> MultiOut [E]) -> GE E -> GE (MultiOut [E])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> D -> GE E
unD D
b1
    where f :: E -> MultiOut [E]
f E
a1 = Name -> Specs -> [E] -> MultiOut [E]
mopcs Name
"imagesize" ([Rate
Ir,Rate
Ir],[Rate
Ir]) [E
a1]