Skip to content

Commit

Permalink
etc
Browse files Browse the repository at this point in the history
  • Loading branch information
ejconlon committed Jan 25, 2024
1 parent fff8c6a commit b56b4a2
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 5 deletions.
2 changes: 1 addition & 1 deletion minipat-dirt/minipat-dirt.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ source-repository head
library
exposed-modules:
Minipat.Dirt.Dirt
Minipat.Dirt.OSC
Minipat.Dirt.Osc
Minipat.Dirt.Prelude
Minipat.Dirt.Ref
Minipat.Dirt.Spy
Expand Down
12 changes: 9 additions & 3 deletions minipat-dirt/src/Minipat/Dirt/Osc.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}

module Minipat.Dirt.OSC where
module Minipat.Dirt.Osc where

import Data.Foldable (foldl', for_)
import Control.Exception (Exception)
Expand Down Expand Up @@ -142,8 +142,8 @@ namedPayload :: PrePayload -> Seq Datum
namedPayload = foldl' go Empty . Map.toList where
go !acc (k, v) = acc :|> DatumString k :|> v

playMsg :: Rational -> B.Tape PrePayload -> PosixTime -> M (Maybe Packet)
playMsg cps tape dawn = go1 where
playPkt :: Rational -> B.Tape PrePayload -> PosixTime -> M (Maybe Packet)
playPkt cps tape dawn = go1 where
go1 = do
flip fmap (tapeToPayloads cps tape) $ \case
Nothing -> Nothing
Expand All @@ -158,3 +158,9 @@ playMsg cps tape dawn = go1 where
else
let ty = posixToNtp (addTime originTy td)
in PacketBundle (Bundle ty (Seq.singleton pkt))

helloAddr :: RawAddrPat
helloAddr = "/dirt/hello"

helloPkt :: Packet
helloPkt = PacketMsg (Msg helloAddr Empty)
7 changes: 6 additions & 1 deletion minipat-dirt/src/Minipat/Dirt/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,12 @@ module Minipat.Dirt.Prelude where

import Data.Ratio ((%))
import Data.IORef (IORef, newIORef)
import Dahdit.Network (Conn, HostPort (..), udpClientConn)
import Dahdit.Network (Conn (..), HostPort (..), udpClientConn, runEncoder)
import Network.Socket qualified as NS
import Data.Acquire (Acquire)
import Minipat.Dirt.Ref (ReleaseVar, Ref)
import Minipat.Dirt.Ref qualified as R
import Minipat.Dirt.Osc qualified as O
import Nanotime (PosixTime, currentTime)

-- private con
Expand Down Expand Up @@ -53,3 +54,7 @@ reinitSt st = R.refReplace (stDirt st) (acqDirt (envDirtHp (stEnv st)))
cleanupSt :: St -> IO ()
cleanupSt = R.releaseVarCleanup . stRel

sendHello :: St -> IO ()
sendHello (St _ _ _ ref) = R.refUse ref $ \case
Nothing -> error "Not connected"
Just (Dirt _ (Conn _ enc)) -> runEncoder enc () O.helloPkt

0 comments on commit b56b4a2

Please sign in to comment.