Skip to content
Snippets Groups Projects
Commit 3925cc1a authored by konsumlamm's avatar konsumlamm
Browse files

Use `async` for benchmarks & remove Makefile

parent 34cc1f19
No related branches found
No related tags found
No related merge requests found
module Async where
import Control.Concurrent (forkIO)
import Control.Concurrent.MVar
newtype Async a = Async (MVar a)
async :: IO a -> IO (Async a)
async action = do
mvar <- newEmptyMVar
_ <- forkIO $ do
x <- action
putMVar mvar x
pure (Async mvar)
wait :: Async a -> IO a
wait (Async a) = takeMVar a
{-# LANGUAGE AllowAmbiguousTypes, ScopedTypeVariables, RankNTypes, TypeApplications #-}
import Control.Concurrent.Async
import Control.Monad
import Data.Foldable (traverse_)
import System.Environment
......@@ -11,8 +12,6 @@ import Control.Concurrent.STM
import Control.Concurrent.STM.TQueue
import Control.Concurrent.STM.TBQueue
import Async
class Channel c where
newc :: IO (c a)
readc :: c a -> IO a
......
GHC=ghc
# Run chanbench for 4 different channel types, 3 different benchmarks
all:
for i in CHAN TCHAN TQUEUE TBQUEUE; do $(GHC) -D$$i -O2 -fforce-recomp chanbench.hs -o chanbench-$$i; done
for i in 0 1 2; do echo; echo === test $$i ===; for j in CHAN TCHAN TQUEUE TBQUEUE; do printf "%-10s" $$j; time ./chanbench-$$j $$i 2000000; done; done
......@@ -13,8 +13,6 @@ description:
benchmark chanbench
type: exitcode-stdio-1.0
main-is: ChanBench.hs
other-modules:
Async
build-depends: base, stm, tasty, tasty-bench
build-depends: base, stm, async, tasty, tasty-bench
default-language: Haskell2010
ghc-options: -O2 -threaded -with-rtsopts=-N
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment