Skip to content

Commit

Permalink
Estuary.Render.ForeignTempo uses JS BigInts (cast via strings) in rep…
Browse files Browse the repository at this point in the history
…resentation of frequency and count values
  • Loading branch information
dktr0 committed Oct 4, 2023
1 parent 355ab5e commit 580b424
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 13 deletions.
4 changes: 2 additions & 2 deletions client/src/Estuary/Languages/ExoLang.hs
Original file line number Diff line number Diff line change
Expand Up @@ -126,12 +126,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
-- let t' = toForeignTempo t
t' <- toForeignTempoDebug t
putStrLn $ "t' " ++ unpack (showForeignTempo t')
_setTempo t' elo -}


foreign import javascript unsafe
"$2.setTempo($1)"
_setTempo :: ForeignTempo -> ExoLangClass -> IO ()
Expand Down
39 changes: 28 additions & 11 deletions 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,showForeignTempo) where
module Estuary.Render.ForeignTempo (ForeignTempo(..), toForeignTempo, toForeignTempoDebug, 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,7 +10,7 @@ import Data.Ratio
import GHCJS.DOM.Types hiding (Text)
import Estuary.Types.Tempo
import Data.Time.Clock.POSIX
import Data.Text (Text)
import Data.Text (Text, pack)

newtype ForeignTempo = ForeignTempo JSVal

Expand All @@ -19,19 +19,36 @@ instance PToJSVal ForeignTempo where pToJSVal (ForeignTempo x) = x
instance PFromJSVal ForeignTempo where pFromJSVal = ForeignTempo

foreign import javascript unsafe
"{ freqNumerator: $1, freqDenominator: $2, time: $3, countNumerator: $4, countDenominator: $5 }"
_newForeignTempo :: Int -> Int -> Double -> Int -> Int -> ForeignTempo
"{ freqNumerator: BigInt($1), freqDenominator: BigInt($2), time: $3, countNumerator: BigInt($4), countDenominator: BigInt($5) }"
_newForeignTempo :: Text -> Text -> Double -> Text -> Text -> ForeignTempo

toForeignTempo :: Tempo -> ForeignTempo
toForeignTempo t = _newForeignTempo freqNumerator freqDenominator time countNumerator countDenominator
where
freqRatioInt = fromRational (freq t) :: Ratio Int
freqNumerator = numerator freqRatioInt
freqDenominator = denominator freqRatioInt
time = realToFrac (utcTimeToPOSIXSeconds $ Estuary.Types.Tempo.time t) * 1000.0
countRatioInt = fromRational (count t) :: Ratio Int
countNumerator = numerator countRatioInt
countDenominator = denominator countRatioInt
freqNumerator = pack $ show $ numerator $ freq t
freqDenominator = pack $ show $ denominator $ freq t
time = realToFrac (utcTimeToPOSIXSeconds $ Estuary.Types.Tempo.time t)
countNumerator = pack $ show $ numerator $ count t
countDenominator = pack $ show $ denominator $ count t

toForeignTempoDebug :: Tempo -> IO ForeignTempo
toForeignTempoDebug t = do
putStrLn "toForeignTempoDebug"
-- let freqRatioInt = fromRational (freq t) :: Ratio Int
-- putStrLn $ " freqRatioInt " ++ show freqRatioInt
let freqNumerator = pack $ show $ numerator $ freq t
putStrLn $ " freqNumerator " ++ show freqNumerator
let freqDenominator = pack $ show $ denominator $ freq t
putStrLn $ " freqDenominator " ++ show freqDenominator
let time = realToFrac (utcTimeToPOSIXSeconds $ Estuary.Types.Tempo.time t)
putStrLn $ " time " ++ show time
-- let countRatioInt = fromRational (count t) :: Ratio Int
-- putStrLn $ " countRatioInt " ++ show countRatioInt
let countNumerator = pack $ show $ numerator $ count t
putStrLn $ " countNumerator " ++ show countNumerator
let countDenominator = pack $ show $ denominator $ count t
putStrLn $ " countDenominator " ++ show countDenominator
pure $ _newForeignTempo freqNumerator freqDenominator time countNumerator countDenominator

foreign import javascript unsafe
"$1.freqNumerator.toString() + \" \" + $1.freqDenominator.toString() + \" \" + $1.time.toString() + \" \" + $1.countNumerator.toString() + \" \" + $1.countDenominator.toString()"
Expand Down

0 comments on commit 580b424

Please sign in to comment.