Skip to content

Commit

Permalink
Fix RandomWalk, small fixes, Util
Browse files Browse the repository at this point in the history
  • Loading branch information
turion committed Jan 15, 2024
1 parent 1358889 commit 99e29cc
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 19 deletions.
39 changes: 24 additions & 15 deletions rhine-examples/src/RandomWalk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,15 +18,15 @@ import System.Random
import Data.Vector2

-- rhine
import FRP.Rhine hiding (flow, sn, Rhine)
import FRP.Rhine.SN.Free
import FRP.Rhine hiding (Rhine, flow, sn)
import FRP.Rhine.Rhine.Free
import FRP.Rhine.SN.Free

type Point = Vector2 Float

type SimulationClock = Millisecond 1
type DisplayClock = Millisecond 1000
type AppClock = '[StdinClock, SimulationClock, DisplayClock]
type AppClock = '[SimulationClock, StdinClock, DisplayClock]

{- | On every newline, show the current point and the local time.
Also, forward the current point so it can be saved.
Expand All @@ -37,8 +37,7 @@ keyboard = proc currentPoint -> do
debugLocalTime -< ()
returnA -< currentPoint

{- | Every millisecond, go one step up, down, right or left.
-}
-- | Every millisecond, go one step up, down, right or left.
simulation :: ClSF IO SimulationClock () Point
simulation = feedback zeroVector $ proc ((), lastPoint) -> do
direction <- constMCl $ randomRIO (0, 3 :: Int) -< ()
Expand Down Expand Up @@ -77,18 +76,28 @@ debugLocalTime = proc a -> do
arrMCl putStrLn -< "since init: " ++ show sinceInit_ ++ "\nsince start: " ++ show sinceStart_
returnA -< a

-- | In this example, we will always zero-order resample, that is, by keeping the last value
resample ::
( HasClocksOrdered clA clB cls
, Monad m
) =>
FreeSN m cls (At clA Point) (At clB Point)
resample = resampling $ keepLast zeroVector

-- | Wire together all components
mainRhine :: Rhine IO UTCTime AppClock () ()
mainRhine = Rhine
{ clocks = StdinClock .:. waitClock .:. waitClock .:. cnil
, sn = feedbackSN (debugLocalTime ^->> keepLast zeroVector) $ proc (lastPoint, ()) -> do
savedPoint <- resampling (keepLast zeroVector) <<< synchronous keyboard -< lastPoint
currentPoint <- resampling (keepLast zeroVector) <<< synchronous simulation -< pure ()
synchronous display -< (,) <$> savedPoint <*> currentPoint
returnA -< (currentPoint, ())
}
-- feedbackRhine (debugLocalTime ^->> keepLast zeroVector) $
-- keyboard @@ StdinClock >-- keepLast zeroVector --> simulation @@ waitClock >-- keepLast (zeroVector, zeroVector) --> display @@ waitClock
mainRhine =
Rhine
-- The order of the clocks matters!
-- Since we are using the `simulation` first, we need to list its clock first.
{ clocks = waitClock .:. StdinClock .:. waitClock .:. cnil
, sn = proc () -> do
currentPoint <- synchronous simulation -< pure ()
savedPoint <- resample <<< synchronous keyboard <<< resample -< currentPoint
currentPointDisplay <- resample -< currentPoint
synchronous display -< (,) <$> savedPoint <*> currentPointDisplay
returnA -< ()
}

-- | Execute the main Rhine
main :: IO ()
Expand Down
9 changes: 5 additions & 4 deletions rhine/src/FRP/Rhine/SN/Free.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module FRP.Rhine.SN.Free (
Append,
Position, -- FIXME this should be internal
HasClock (..),
HasClocksOrdered (..),
runClocks,
-- FIXME the followong are probably internal
appendClocks,
Expand Down Expand Up @@ -175,10 +176,7 @@ synchronous :: (HasClock cl cls, Clock m cl) => ClSF m cl a b -> FreeSN m cls (A
synchronous = FreeSN . liftFree2 . Synchronous position

resampling ::
( HasClock clA cls
, Clock m clA
, HasClocksOrdered clA clB cls
, HasClock clB cls
( HasClocksOrdered clA clB cls
) =>
ResamplingBuffer m clA clB a b ->
FreeSN m cls (At clA a) (At clB b)
Expand Down Expand Up @@ -269,6 +267,9 @@ infixr 9 .:.
(.:.) :: (GetClockProxy cl, Clock m cl) => cl -> Clocks m (Time cl) cls -> Clocks m (Time cl) (cl ': cls)
getClassyClock .:. Clocks {getClocks} = Clocks $ ClassyClock {getClassyClock} :* getClocks

clocks :: (GetClockProxy cl, Clock m cl) => cl -> Clocks m (Time cl) '[cl]
clocks cl = cl .:. cnil

cnil :: Clocks m td '[]
cnil = Clocks Nil

Expand Down

0 comments on commit 99e29cc

Please sign in to comment.