Skip to content

Commit

Permalink
added showForeignTempo and a (commented out) debugging version of set…
Browse files Browse the repository at this point in the history
…Tempo in Estuary.Languages.ExoLang
  • Loading branch information
dktr0 committed Oct 4, 2023
1 parent 60de54c commit 355ab5e
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 1 deletion.
6 changes: 6 additions & 0 deletions client/src/Estuary/Languages/ExoLang.hs
Original file line number Diff line number Diff line change
Expand Up @@ -125,6 +125,12 @@ foreign import javascript unsafe

setTempo :: ExoLang -> Tempo -> IO ()
setTempo e t = void $ withExoLang e $ _setTempo $ toForeignTempo t
{- setTempo e t = withExoLang e $ \elo -> do
let t' = toForeignTempo t
putStrLn $ "t " ++ show t
putStrLn $ "t' " ++ unpack (showForeignTempo t')
_setTempo t' elo -}


foreign import javascript unsafe
"$2.setTempo($1)"
Expand Down
7 changes: 6 additions & 1 deletion client/src/Estuary/Render/ForeignTempo.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE JavaScriptFFI #-}

module Estuary.Render.ForeignTempo (ForeignTempo(..),toForeignTempo) where
module Estuary.Render.ForeignTempo (ForeignTempo(..),toForeignTempo,showForeignTempo) where

-- | The ForeignTempo type is used to interface with (and is essentially defined by)
-- the purescript-tempi library. toForeignTempo can be used to convert Estuary's
Expand All @@ -10,6 +10,7 @@ import Data.Ratio
import GHCJS.DOM.Types hiding (Text)
import Estuary.Types.Tempo
import Data.Time.Clock.POSIX
import Data.Text (Text)

newtype ForeignTempo = ForeignTempo JSVal

Expand All @@ -31,3 +32,7 @@ toForeignTempo t = _newForeignTempo freqNumerator freqDenominator time countNume
countRatioInt = fromRational (count t) :: Ratio Int
countNumerator = numerator countRatioInt
countDenominator = denominator countRatioInt

foreign import javascript unsafe
"$1.freqNumerator.toString() + \" \" + $1.freqDenominator.toString() + \" \" + $1.time.toString() + \" \" + $1.countNumerator.toString() + \" \" + $1.countDenominator.toString()"
showForeignTempo :: ForeignTempo -> Text

0 comments on commit 355ab5e

Please sign in to comment.