Skip to content

Instantly share code, notes, and snippets.

@mstksg
Created July 31, 2014 05:05
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save mstksg/278c43f4a825af9523a0 to your computer and use it in GitHub Desktop.
Save mstksg/278c43f4a825af9523a0 to your computer and use it in GitHub Desktop.
Example of stepping/running an Wire with constant dt
{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Main (main) where
import Control.Wire
import FRP.Netwire.Move
import Control.Arrow
import Prelude hiding ((.), id, mapM_)
import Data.Foldable
import Control.Category
import Control.Monad.Fix
dt :: Double
dt = 0.01
sho :: (HasTime Double s, MonadFix m) => Wire s () m a Double
sho = proc _ -> do
rec let a = -0.5 * x
v <- integral 0 -< a
x <- integral 1 -< v
returnA -< x
stepShow :: Int -> Wire (Timed Double ()) () IO () Double -> IO ()
stepShow 0 _ = return ()
stepShow n a = do
(ds, _) <- stepSession (countSession dt <*> pure ())
(r, a') <- stepWire a ds (Right ())
mapM_ print r
stepShow (n-1) a'
main :: IO ()
main = stepShow 1001 sho
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment