-- | A @VividAction m => m a@ can either be run immediately, be scheduled to run at a
--   precise future time, or be used for non-realtime synthesis.
-- 
--   Note that at the moment VividAction has MonadIO, but this won't be true in
--   upcoming versions (as early as the next release) - so don't get used
--   to it!

{-# LANGUAGE
     KindSignatures
   , Rank2Types
   #-}

{-# LANGUAGE NoIncoherentInstances #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE NoUndecidableInstances #-}

module Vivid.Actions.Class (
     VividAction(..)
   -- , VA
   , callOSCAndSync
   , oscWSync
   ) where

import Vivid.SC.Server.Types (BufferId, NodeId, SyncId(..))
import qualified Vivid.SC.Server.Commands as SCCmd

import Vivid.OSC
import Vivid.SynthDef.Types (SynthDef)

import Control.Monad.IO.Class (MonadIO)
import Data.ByteString (ByteString)

class (Monad m , MonadIO m) => VividAction (m :: * -> *) where

   -- | Send an 'OSC' message to the SuperCollider server
   callOSC :: OSC -> m ()
   callOSC = ByteString -> m ()
forall (m :: * -> *). VividAction m => ByteString -> m ()
callBS (ByteString -> m ()) -> (OSC -> ByteString) -> OSC -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OSC -> ByteString
encodeOSC

   -- | Send a ByteString to the SuperCollider server.
   --   You usually want to use 'call' instead.
   callBS :: ByteString -> m ()

   -- | Blocks until the server finishes processing commands
   sync :: m ()

   -- | As the user, you probably don't want to use this:
   -- 
   --   Many commands already include a \"sync\" -- e.g.
   --   'makeBuffer' already syncs.
   -- 
   --   When you do want to do an
   --   explicit sync you probably want to use 'sync' instead, or
   --   'callOSCAndSync'
   waitForSync :: SyncId -> m ()

   -- | Wait, in seconds
   wait :: Real n => n -> m ()

   getTime :: m Timestamp

   newBufferId :: m BufferId

   newNodeId :: m NodeId

   newSyncId :: m SyncId

   fork :: m () -> m ()

   -- | Send a synth definition to be loaded on the SC server
   -- 
   --   Note that this is sort of optional -- if you don't call it, it'll be called the first time
   --   you call 'synth' with the SynthDef
   defineSD :: SynthDef a -> m ()

-- | Send an OSC message and wait for it to complete before returning
callOSCAndSync :: VividAction m => OSC -> m ()
callOSCAndSync :: OSC -> m ()
callOSCAndSync OSC
message = do
   Timestamp
now <- m Timestamp
forall (m :: * -> *). VividAction m => m Timestamp
getTime
   SyncId
syncId <- m SyncId
forall (m :: * -> *). VividAction m => m SyncId
newSyncId
   ByteString -> m ()
forall (m :: * -> *). VividAction m => ByteString -> m ()
callBS (ByteString -> m ()) -> ByteString -> m ()
forall a b. (a -> b) -> a -> b
$ OSCBundle -> ByteString
encodeOSCBundle (OSCBundle -> ByteString) -> OSCBundle -> ByteString
forall a b. (a -> b) -> a -> b
$
      Timestamp -> [Either ByteString OSC] -> OSCBundle
OSCBundle Timestamp
now [OSC -> Either ByteString OSC
forall a b. b -> Either a b
Right OSC
message, OSC -> Either ByteString OSC
forall a b. b -> Either a b
Right (OSC -> Either ByteString OSC) -> OSC -> Either ByteString OSC
forall a b. (a -> b) -> a -> b
$ SyncId -> OSC
SCCmd.sync SyncId
syncId]
   SyncId -> m ()
forall (m :: * -> *). VividAction m => SyncId -> m ()
waitForSync SyncId
syncId

-- | 
-- 
--   Maybe can dedupe with 'callOSCAndSync'
oscWSync :: VividAction m => (SyncId -> m ()) -> m ()
oscWSync :: (SyncId -> m ()) -> m ()
oscWSync SyncId -> m ()
actionFromId = do
   SyncId
syncId <- m SyncId
forall (m :: * -> *). VividAction m => m SyncId
newSyncId
   SyncId -> m ()
actionFromId SyncId
syncId
   SyncId -> m ()
forall (m :: * -> *). VividAction m => SyncId -> m ()
waitForSync SyncId
syncId


-- type VA x = forall m. VividAction m => m x