Skip to content
This repository has been archived by the owner on Apr 1, 2022. It is now read-only.

Commit

Permalink
Don't use CPP
Browse files Browse the repository at this point in the history
  • Loading branch information
cnr committed Oct 22, 2021
1 parent 79786fe commit 0a7452c
Showing 1 changed file with 15 additions and 16 deletions.
31 changes: 15 additions & 16 deletions test/System/CGroup/TypesSpec.hs
Original file line number Diff line number Diff line change
@@ -1,53 +1,52 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}

module System.CGroup.TypesSpec (
spec,
) where

-- This test won't work on Windows (mingw32), because paths starting with `/` are invalid
#ifndef mingw32_HOST_OS
import Path
import Path.IO (getCurrentDir, resolveFile)
import System.CGroup.Types
import System.Info (os)
import Test.Hspec (Spec, describe, it, runIO, shouldBe)

-- This test won't work on Windows, because paths starting with `/` are invalid
spec :: Spec
spec = do
spec = exceptOnWindows $ do
currentDir <- runIO getCurrentDir

describe "resolveGroupController" $ do
it "should work on a real world example" $ do
cgroup <- resolveFile currentDir "test/System/CGroup/testdata/realworld/cgroup"
mountinfo <- resolveFile currentDir "test/System/CGroup/testdata/realworld/mountinfo"
expected <- parseAbsDir "/sys/fs/cgroup/cpu"

controller <- resolveCGroupController' cgroup mountinfo "cpu"
controller `shouldBe` Controller $(mkAbsDir "/sys/fs/cgroup/cpu")
controller `shouldBe` Controller expected

it "should resolve a direct mount root" $ do
cgroup <- resolveFile currentDir "test/System/CGroup/testdata/direct/cgroup"
mountinfo <- resolveFile currentDir "test/System/CGroup/testdata/direct/mountinfo"
expected <- parseAbsDir "/sys/fs/cgroup/cpu"

controller <- resolveCGroupController' cgroup mountinfo "cpu"
controller `shouldBe` Controller $(mkAbsDir "/sys/fs/cgroup/cpu")
controller `shouldBe` Controller expected

it "should resolve subdirectories of a mount root" $ do
cgroup <- resolveFile currentDir "test/System/CGroup/testdata/indirect/cgroup"
mountinfo <- resolveFile currentDir "test/System/CGroup/testdata/indirect/mountinfo"
expected <- parseAbsDir "/sys/fs/cgroup/cpu/subdir"

controller <- resolveCGroupController' cgroup mountinfo "cpu"
controller `shouldBe` Controller $(mkAbsDir "/sys/fs/cgroup/cpu/subdir")
controller `shouldBe` Controller expected

it "should work for cgroups v2" $ do
cgroup <- resolveFile currentDir "test/System/CGroup/testdata/cgroupsv2/cgroup"
mountinfo <- resolveFile currentDir "test/System/CGroup/testdata/cgroupsv2/mountinfo"
expected <- parseAbsDir "/sys/fs/cgroup/cpu"

controller <- resolveCGroupController' cgroup mountinfo "cpu"
controller `shouldBe` Controller $(mkAbsDir "/sys/fs/cgroup/cpu")
#else
import Test.Hspec (Spec)
controller `shouldBe` Controller expected

-- Windows: do nothing
spec :: Spec
spec = pure ()
#endif
exceptOnWindows :: Applicative m => m () -> m ()
exceptOnWindows act
| os == "mingw32" = pure ()
| otherwise = act

0 comments on commit 0a7452c

Please sign in to comment.