Skip to content

Commit

Permalink
Various CI fixes (#428)
Browse files Browse the repository at this point in the history
* Enable tests and benchmarks by default

This is usually what you want and ensures that CI will build things.

* Disable aarch64-linux on hydra for now

* Remove cicero

* Fix cardano-mempool benchmarks

---------

Co-authored-by: Alexey Kuleshevich <alexey.kuleshevich@iohk.io>
  • Loading branch information
michaelpj and lehins authored Jul 26, 2023
1 parent 35cd5cf commit 307e22c
Show file tree
Hide file tree
Showing 4 changed files with 80 additions and 124 deletions.
3 changes: 3 additions & 0 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,9 @@ packages:
-- Ensures colourized output from test runners
test-show-details: direct

tests: true
benchmarks: true

program-options
ghc-options: -Werror

Expand Down
54 changes: 30 additions & 24 deletions cardano-mempool/bench/Bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,25 +2,28 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Main where

import Foreign.Marshal.Alloc
import GHC.TypeLits
import Criterion.Main
import Cardano.Memory.Pool
import Foreign.ForeignPtr
import Control.DeepSeq
import UnliftIO.Async (pooledReplicateConcurrently)
import Control.Monad
import Control.Monad.ST (RealWorld, stToIO)
import Criterion.Main
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
import GHC.IO (ioToST)
import GHC.TypeLits
import UnliftIO.Async (pooledReplicateConcurrently)

instance NFData (Pool n) where
instance NFData (Pool n s) where
rnf !_ = ()

instance NFData (ForeignPtr a) where
rnf !_ = ()

initHaskellPool :: KnownNat n => Int -> IO (Pool n)
initHaskellPool n = initPool n mallocForeignPtrBytes (const (pure ()))
initHaskellPool :: (KnownNat n) => Int -> IO (Pool n RealWorld)
initHaskellPool n = stToIO $ initPool n (ioToST . mallocForeignPtrBytes) (const (pure ()))

cmallocForeignPtr :: Int -> IO (ForeignPtr a)
cmallocForeignPtr n = do
Expand All @@ -32,20 +35,23 @@ main = do
let n = 10240
blockSize = 32
defaultMain
[ bgroup "Sequential"
[ env (initHaskellPool @32 (n `div` 64)) $ \pool ->
bench "ForeignPtr (Pool)" $ nfIO (replicateM n (grabNextBlock pool))
, bench "ForeignPtr (ByteArray)" $
nfIO (replicateM n (mallocForeignPtrBytes blockSize))
, bench "ForeignPtr (malloc)" $
nfIO (replicateM n (cmallocForeignPtr blockSize))
]
, bgroup "Concurrent"
[ env (initHaskellPool @32 (n `div` 64)) $ \pool ->
bench "ForeignPtr (Pool)" $ nfIO (pooledReplicateConcurrently n (grabNextBlock pool))
, bench "ForeignPtr (ByteArray)" $
nfIO (pooledReplicateConcurrently n (mallocForeignPtrBytes blockSize))
, bench "ForeignPtr (malloc)" $
nfIO (pooledReplicateConcurrently n (cmallocForeignPtr blockSize))
]
[ bgroup
"Sequential"
[ env (initHaskellPool @32 (n `div` 64)) $ \pool ->
bench "ForeignPtr (Pool)" $ nfIO $ replicateM n (stToIO (grabNextBlock pool))
, bench "ForeignPtr (ByteArray)" $
nfIO (replicateM n (mallocForeignPtrBytes blockSize))
, bench "ForeignPtr (malloc)" $
nfIO (replicateM n (cmallocForeignPtr blockSize))
]
, bgroup
"Concurrent"
[ env (initHaskellPool @32 (n `div` 64)) $ \pool ->
bench "ForeignPtr (Pool)" $
nfIO (pooledReplicateConcurrently n (stToIO (grabNextBlock pool)))
, bench "ForeignPtr (ByteArray)" $
nfIO (pooledReplicateConcurrently n (mallocForeignPtrBytes blockSize))
, bench "ForeignPtr (malloc)" $
nfIO (pooledReplicateConcurrently n (cmallocForeignPtr blockSize))
]
]
85 changes: 45 additions & 40 deletions flake.lock

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit 307e22c

Please sign in to comment.