{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -Wno-redundant-constraints #-} {-| Description: Copyright: (c) 2019-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: experimental Portability: portable -} module Test.Libcdio.Property.Common where import qualified Data.String as S import qualified Data.Text as T import qualified Hedgehog as H import qualified Hedgehog.Gen as H.G import qualified Hedgehog.Classes as H.C import qualified Hedgehog.Range as H.R import qualified Foreign.Storable as S type Test = (H.PropertyName, H.Property) type LawsGroup = (String, [H.C.Laws]) enumSparse :: (Enum a, Bounded a) => H.Gen a enumSparse = H.G.element [minBound..maxBound] nonZero :: (Eq a, Num a) => H.Gen a -> H.Gen a nonZero = H.G.filter (/= 0) packTest :: String -> H.PropertyT IO () -> Test packTest name prop = (S.fromString name, H.property prop) genSample :: H.Gen T.Text genSample = H.G.text (H.R.linear 1 12) $ H.G.frequency [c7, c8] where c7 = (0x5F, H.G.enum ' ' '~') c8 = (0x60, H.G.enum '\xA0' '\xFF') ordLaws' :: (Ord a, Show a) => H.Gen a -> H.C.Laws #if MIN_VERSION_hedgehog_classes(0,2,1) ordLaws' = H.C.ordLaws #else ordLaws' = const $ H.C.Laws "Ord" [] #endif storableLaws' :: (Eq a, Show a, S.Storable a) => H.Gen a -> H.C.Laws #if MIN_VERSION_hedgehog_classes(0,2,6) storableLaws' = H.C.storableLaws #else storableLaws' = const $ H.C.Laws "Storable" [] #endif