module Csound.Typed.Control.Osc(
    OscRef, OscHost, OscPort, OscAddress, OscType, 
    initOsc, listenOsc, sendOsc
) where
import Data.Boolean ((==*))
import Csound.Typed.Types
import Csound.Typed.GlobalState hiding (oscInit, oscListen, oscSend)
import qualified Csound.Typed.GlobalState as C(oscInit, oscListen, oscSend)
import Csound.Typed.Control.SERef
newtype OscRef = OscRef { unOscRef :: D }
type OscPort = Int
type OscAddress = String
 
type OscType = String
type OscHost = String
initOsc :: OscPort -> SE OscRef
initOsc port = do
    oscRef <- fmap fromGE $ fromDep $ C.oscInit (fromIntegral port)
    varRef <- newGlobalSERef (0 :: D)
    writeSERef varRef oscRef
    ihandle <- readSERef varRef
    return $ OscRef ihandle
listenOsc :: forall a . Tuple a => OscRef -> OscAddress -> OscType -> Evt a
listenOsc oscRef oscAddr oscType = Evt $ \bam -> do
    (readCond, writeCond) <- sensorsSE (0 :: Sig)
    resRef <- newSERef (defTuple :: a)
    writeCond =<< listen resRef
    readCond >>= (\cond -> whileDo (cond ==* 1) $ do
        bam =<< readSERef resRef
        writeCond =<< listen resRef)
    where
        listen :: Tuple a => SERef a -> SE Sig
        listen ref = csdOscListen ref oscRef oscAddr oscType
        csdOscListen :: Tuple a => SERef a -> OscRef -> OscAddress -> OscType -> SE Sig
        csdOscListen resRef oscHandle addr ty = do
            args <- readSERef resRef
            res  <- fmap fromGE $ fromDep $ hideGEinDep $ do 
                expArgs <- fromTuple args
                expOscHandle <- toGE $ unOscRef oscHandle
                expAddr <- toGE $ text addr
                expOscType <- toGE $ text ty
                return $ C.oscListen $ expOscHandle : expAddr : expOscType : expArgs
            writeSERef resRef args
            return res
sendOsc :: forall a . Tuple a => OscHost -> OscPort -> OscAddress -> OscType -> Evt a -> SE ()
sendOsc host port addr ty evts = runEvt evts send
    where 
        send :: Tuple a => a -> SE ()
        send as = SE $ hideGEinDep $ do
            args <- fromTuple as
            expHost <- toGE $ text $ host
            expPort <- toGE $ int  $ port
            expAddr <- toGE $ text $ addr
            expTy   <- toGE $ text $ ty
            return $ C.oscSend $ 1 : expHost : expPort : expAddr : expTy : args