11{-# LANGUAGE NumericUnderscores #-}
22{-# LANGUAGE OverloadedStrings #-}
33
4- module SerializeSpec where
4+ module SerializeSpec ( spec ) where
55
6- import Data.ByteString (ByteString )
76import Data.Fixed (Uni )
8- import Data.HashSet (HashSet )
97import Data.Serialize (Serialize (.. ))
108import Data.Serialize.Get (Get , runGet )
119import Data.Serialize.Put (Putter , runPut )
1210import Data.Text (Text )
1311import Data.Time (NominalDiffTime )
14- import Test.Hspec (Spec , describe , it , shouldBe )
15- import Test.Tasty.QuickCheck
12+ import Test.Hspec (Expectation , Spec , describe , it , shouldBe )
13+ import Test.Hspec.QuickCheck (prop )
14+ import Test.Hspec.Nix (roundtrips )
15+ import Test.QuickCheck (arbitrary , forAll , suchThat )
1616import Test.QuickCheck.Instances ()
1717
1818import qualified Data.Either
@@ -23,139 +23,110 @@ import qualified System.Nix.Build
2323import System.Nix.Arbitrary ()
2424import System.Nix.Build (BuildMode , BuildStatus )
2525import System.Nix.Derivation (Derivation (.. ))
26- import System.Nix.StorePath (StoreDir , StorePath )
2726import System.Nix.Store.Remote.Serialize (getDerivation , putDerivation )
2827import System.Nix.Store.Remote.Serialize.Prim
2928
30- roundTrip :: (Eq a , Show a ) => Putter a -> Get a -> a -> Property
31- roundTrip p g a = res === Right a
32- where res = runGet g (runPut (p a))
29+ -- | Test for roundtrip using @Putter@ and @Get@ functions
30+ roundtrips2
31+ :: ( Eq a
32+ , Show a
33+ )
34+ => Putter a
35+ -> Get a
36+ -> a
37+ -> Expectation
38+ roundtrips2 putter getter =
39+ roundtrips
40+ (runPut . putter)
41+ (runGet getter)
42+
43+ -- | Test for roundtrip using @Serialize@ instance
44+ roundtripS
45+ :: ( Eq a
46+ , Serialize a
47+ , Show a
48+ )
49+ => a
50+ -> Expectation
51+ roundtripS =
52+ roundtrips
53+ (runPut . put)
54+ (runGet get)
55+
56+ spec :: Spec
57+ spec = do
58+ describe " Prim" $ do
59+ prop " Int" $ roundtrips2 putInt getInt
60+ prop " Bool" $ roundtrips2 putBool getBool
61+
62+ prop " UTCTime" $ do
63+ let
64+ -- scale to seconds and back
65+ toSeconds :: Int -> NominalDiffTime
66+ toSeconds n = realToFrac (toEnum n :: Uni )
67+ fromSeconds :: NominalDiffTime -> Int
68+ fromSeconds = (fromEnum :: Uni -> Int ) . realToFrac
69+
70+ roundtrips2
71+ (putTime . Data.Time.Clock.POSIX. posixSecondsToUTCTime . toSeconds)
72+ (fromSeconds . Data.Time.Clock.POSIX. utcTimeToPOSIXSeconds <$> getTime)
73+
74+ describe " Combinators" $ do
75+ prop " Many" $ roundtrips2 (putMany putInt) (getMany getInt)
76+ prop " ByteString" $ roundtrips2 putByteString getByteString
77+ prop " [ByteString]" $ roundtrips2 putByteStrings getByteStrings
78+ prop " Text" $ roundtrips2 putText getText
79+ prop " [Text]" $ roundtrips2 putTexts getTexts
80+
81+ prop " StorePath" $ \ sd ->
82+ roundtrips2
83+ (putPath sd)
84+ (Data.Either. fromRight undefined <$> getPath sd)
85+
86+ prop " HashSet StorePath" $ \ sd ->
87+ roundtrips2
88+ (putPaths sd)
89+ (Data.HashSet. map (Data.Either. fromRight undefined ) <$> getPaths sd)
90+
91+ describe " Serialize instances" $ do
92+ prop " Text" $ roundtripS @ Text
93+ prop " BuildMode" $ roundtripS @ BuildMode
94+ prop " BuildStatus" $ roundtripS @ BuildStatus
95+ it " BuildResult" $
96+ forAll (arbitrary `suchThat` ((/= Just " " ) . System.Nix.Build. errorMessage))
97+ $ \ br ->
98+ roundtripS
99+ -- fix time to 0 as we test UTCTime above
100+ $ br { System.Nix.Build. startTime = Data.Time.Clock.POSIX. posixSecondsToUTCTime 0
101+ , System.Nix.Build. stopTime = Data.Time.Clock.POSIX. posixSecondsToUTCTime 0
102+ }
103+
104+ prop " Derivation StorePath Text" $ \ sd ->
105+ roundtrips2
106+ (putDerivation sd)
107+ (getDerivation sd)
108+ -- inputDrvs is not used in remote protocol serialization
109+ . (\ drv -> drv { inputDrvs = mempty })
33110
34- -- * Prim
35- -- ** Int
36-
37- prop_int :: Int -> Property
38- prop_int = roundTrip putInt getInt
39-
40- -- ** Bool
41-
42- prop_bool :: Bool -> Property
43- prop_bool = roundTrip putBool getBool
44-
45- -- ** UTCTime
46-
47- prop_time :: Int -> Property
48- prop_time =
49- roundTrip
50- (putTime . Data.Time.Clock.POSIX. posixSecondsToUTCTime . toSeconds)
51- (fromSeconds . Data.Time.Clock.POSIX. utcTimeToPOSIXSeconds <$> getTime)
52- where
53- -- scale to seconds and back
54- toSeconds :: Int -> NominalDiffTime
55- toSeconds n = realToFrac (toEnum n :: Uni )
56- fromSeconds :: NominalDiffTime -> Int
57- fromSeconds = (fromEnum :: Uni -> Int ) . realToFrac
58-
59- -- ** Combinators
60-
61- prop_many :: [Int ] -> Property
62- prop_many = roundTrip (putMany putInt) (getMany getInt)
63-
64- -- ** ByteString
65-
66- prop_bytestring :: ByteString -> Property
67- prop_bytestring = roundTrip putByteString getByteString
68-
69- prop_bytestrings :: [ByteString ] -> Property
70- prop_bytestrings = roundTrip putByteStrings getByteStrings
71-
72- -- ** Text
73-
74- prop_text :: Text -> Property
75- prop_text = roundTrip putText getText
76-
77- prop_texts :: [Text ] -> Property
78- prop_texts = roundTrip putTexts getTexts
79-
80- -- ** StorePath
81-
82- prop_path :: StoreDir -> StorePath -> Property
83- prop_path = \ sd ->
84- roundTrip
85- (putPath sd)
86- (Data.Either. fromRight undefined <$> getPath sd)
87-
88- prop_paths :: StoreDir -> HashSet StorePath -> Property
89- prop_paths = \ sd ->
90- roundTrip
91- (putPaths sd)
92- (Data.HashSet. map (Data.Either. fromRight undefined ) <$> getPaths sd)
93-
94- -- * Serialize
95- roundTripS :: (Eq a , Serialize a , Show a ) => a -> Property
96- roundTripS a = res === Right a
97- where res = runGet get (runPut (put a))
98-
99- -- ** Text
100-
101- prop_Text :: Text -> Property
102- prop_Text = roundTripS
103-
104- -- ** BuildMode
105-
106- prop_buildMode :: BuildMode -> Property
107- prop_buildMode = roundTripS
108-
109- -- ** BuildStatus
110-
111- prop_buildStatus :: BuildStatus -> Property
112- prop_buildStatus = roundTripS
113-
114- -- ** BuildResult
115-
116- prop_buildResult :: Property
117- prop_buildResult =
118- forAll (arbitrary `suchThat` ((/= Just " " ) . System.Nix.Build. errorMessage))
119- $ \ br ->
120- roundTripS
121- $ br { System.Nix.Build. startTime = Data.Time.Clock.POSIX. posixSecondsToUTCTime 0
122- , System.Nix.Build. stopTime = Data.Time.Clock.POSIX. posixSecondsToUTCTime 0
123- }
124-
125- -- ** Enums
126-
127- spec_buildEnums :: Spec
128- spec_buildEnums =
129111 let it' name constr value = it name $ runPut (put constr) `shouldBe` runPut (putInt value)
130- in do
131- describe " Build enum order matches Nix" $ do
132- it' " Normal" System.Nix.Build. Normal 0
133- it' " Repair" System.Nix.Build. Repair 1
134- it' " Check" System.Nix.Build. Check 2
135-
136- describe " BuildStatus enum order matches Nix" $ do
137- it' " Built" System.Nix.Build. Built 0
138- it' " Substituted" System.Nix.Build. Substituted 1
139- it' " AlreadyValid" System.Nix.Build. AlreadyValid 2
140- it' " PermanentFailure" System.Nix.Build. PermanentFailure 3
141- it' " InputRejected" System.Nix.Build. InputRejected 4
142- it' " OutputRejected" System.Nix.Build. OutputRejected 5
143- it' " TransientFailure" System.Nix.Build. TransientFailure 6
144- it' " CachedFailure" System.Nix.Build. CachedFailure 7
145- it' " TimedOut" System.Nix.Build. TimedOut 8
146- it' " MiscFailure" System.Nix.Build. MiscFailure 9
147- it' " DependencyFailed" System.Nix.Build. DependencyFailed 10
148- it' " LogLimitExceeded" System.Nix.Build. LogLimitExceeded 11
149- it' " NotDeterministic" System.Nix.Build. NotDeterministic 12
150- it' " ResolvesToAlreadyValid" System.Nix.Build. ResolvesToAlreadyValid 13
151- it' " NoSubstituters" System.Nix.Build. NoSubstituters 14
152-
153- -- ** Derivation
154-
155- prop_derivation :: StoreDir -> Derivation StorePath Text -> Property
156- prop_derivation sd drv =
157- roundTrip
158- (putDerivation sd)
159- (getDerivation sd)
160- -- inputDrvs is not used in remote protocol serialization
161- (drv { inputDrvs = mempty })
112+ describe " Build enum order matches Nix" $ do
113+ it' " Normal" System.Nix.Build. Normal 0
114+ it' " Repair" System.Nix.Build. Repair 1
115+ it' " Check" System.Nix.Build. Check 2
116+
117+ describe " BuildStatus enum order matches Nix" $ do
118+ it' " Built" System.Nix.Build. Built 0
119+ it' " Substituted" System.Nix.Build. Substituted 1
120+ it' " AlreadyValid" System.Nix.Build. AlreadyValid 2
121+ it' " PermanentFailure" System.Nix.Build. PermanentFailure 3
122+ it' " InputRejected" System.Nix.Build. InputRejected 4
123+ it' " OutputRejected" System.Nix.Build. OutputRejected 5
124+ it' " TransientFailure" System.Nix.Build. TransientFailure 6
125+ it' " CachedFailure" System.Nix.Build. CachedFailure 7
126+ it' " TimedOut" System.Nix.Build. TimedOut 8
127+ it' " MiscFailure" System.Nix.Build. MiscFailure 9
128+ it' " DependencyFailed" System.Nix.Build. DependencyFailed 10
129+ it' " LogLimitExceeded" System.Nix.Build. LogLimitExceeded 11
130+ it' " NotDeterministic" System.Nix.Build. NotDeterministic 12
131+ it' " ResolvesToAlreadyValid" System.Nix.Build. ResolvesToAlreadyValid 13
132+ it' " NoSubstituters" System.Nix.Build. NoSubstituters 14
0 commit comments