Skip to content

Commit 7bdbab9

Browse files
committed
remote: move enum tests to EnumSpec
1 parent 428a61a commit 7bdbab9

File tree

5 files changed

+147
-97
lines changed

5 files changed

+147
-97
lines changed

hnix-store-remote/hnix-store-remote.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -170,6 +170,7 @@ test-suite remote
170170
ghc-options: -Wall -threaded -rtsopts "-with-rtsopts -N"
171171
other-modules:
172172
Data.SerializerSpec
173+
EnumSpec
173174
NixSerializerSpec
174175
SerializeSpec
175176
build-tool-depends:
@@ -179,6 +180,7 @@ test-suite remote
179180
, hnix-store-core
180181
, hnix-store-remote
181182
, hnix-store-tests
183+
, bytestring
182184
, cereal
183185
, crypton
184186
, some > 1.0.5 && < 2

hnix-store-remote/src/System/Nix/Store/Remote/Serializer.hs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@ module System.Nix.Store.Remote.Serializer
6868
, LoggerSError(..)
6969
, activityID
7070
, maybeActivity
71+
, activity
7172
, activityResult
7273
, field
7374
, trace
@@ -886,12 +887,12 @@ maybeActivity = Serializer
886887
Nothing -> putS (int @Int) 0
887888
Just act -> putS activity act
888889
}
889-
where
890-
activity :: NixSerializer r LoggerSError Activity
891-
activity = Serializer
892-
{ getS = mapPrimE $ getS int >>= toEnumCheckBoundsM . (+(-100))
893-
, putS = putS int . (+100) . fromEnum
894-
}
890+
891+
activity :: NixSerializer r LoggerSError Activity
892+
activity = Serializer
893+
{ getS = mapPrimE $ getS int >>= toEnumCheckBoundsM . (+(-100))
894+
, putS = putS int . (+100) . fromEnum
895+
}
895896

896897
activityID :: NixSerializer r LoggerSError ActivityID
897898
activityID = mapIsoSerializer ActivityID unActivityID int
Lines changed: 136 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,136 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
module EnumSpec (spec) where
4+
5+
import Test.Hspec (SpecWith, Spec, describe, it, shouldBe)
6+
7+
import Data.ByteString (ByteString)
8+
import Data.Word (Word64)
9+
import System.Nix.Build (BuildMode(..), BuildStatus(..))
10+
import System.Nix.Store.Remote.Serializer
11+
( activity
12+
, activityResult
13+
, enum
14+
, int
15+
, loggerOpCode
16+
, runP
17+
, LoggerSError
18+
, NixSerializer
19+
, SError
20+
)
21+
import System.Nix.Store.Remote.Types
22+
23+
spec :: Spec
24+
spec = do
25+
let
26+
itE
27+
:: ( Enum a
28+
, Show a
29+
)
30+
=> String
31+
-> a
32+
-> Word64
33+
-> SpecWith ()
34+
itE name constr value =
35+
it name
36+
$ ((runP enum () constr) :: Either SError ByteString)
37+
`shouldBe`
38+
(runP (int @Word64) () value)
39+
40+
itE'
41+
:: Show a
42+
=> NixSerializer () LoggerSError a
43+
-> String
44+
-> a
45+
-> Word64
46+
-> SpecWith ()
47+
itE' s name constr value =
48+
it name
49+
$ ((runP s () constr) :: Either LoggerSError ByteString)
50+
`shouldBe`
51+
(runP (int @Word64) () (value))
52+
53+
describe "Enums" $ do
54+
describe "BuildMode enum order matches Nix" $ do
55+
itE "Normal" BuildMode_Normal 0
56+
itE "Repair" BuildMode_Repair 1
57+
itE "Check" BuildMode_Check 2
58+
59+
describe "BuildStatus enum order matches Nix" $ do
60+
itE "Built" BuildStatus_Built 0
61+
itE "Substituted" BuildStatus_Substituted 1
62+
itE "AlreadyValid" BuildStatus_AlreadyValid 2
63+
itE "PermanentFailure" BuildStatus_PermanentFailure 3
64+
itE "InputRejected" BuildStatus_InputRejected 4
65+
itE "OutputRejected" BuildStatus_OutputRejected 5
66+
itE "TransientFailure" BuildStatus_TransientFailure 6
67+
itE "CachedFailure" BuildStatus_CachedFailure 7
68+
itE "TimedOut" BuildStatus_TimedOut 8
69+
itE "MiscFailure" BuildStatus_MiscFailure 9
70+
itE "DependencyFailed" BuildStatus_DependencyFailed 10
71+
itE "LogLimitExceeded" BuildStatus_LogLimitExceeded 11
72+
itE "NotDeterministic" BuildStatus_NotDeterministic 12
73+
itE "ResolvesToAlreadyValid" BuildStatus_ResolvesToAlreadyValid 13
74+
itE "NoSubstituters" BuildStatus_NoSubstituters 14
75+
76+
describe "GCAction enum order matches Nix" $ do
77+
itE "ReturnLive" GCAction_ReturnLive 0
78+
itE "ReturnDead" GCAction_ReturnDead 1
79+
itE "DeleteDead" GCAction_DeleteDead 2
80+
itE "DeleteSpecific" GCAction_DeleteSpecific 3
81+
82+
describe "Logger" $ do
83+
let itA = itE' activity
84+
describe "Activity enum order matches Nix" $ do
85+
itA "CopyPath" Activity_CopyPath 100
86+
itA "FileTransfer" Activity_FileTransfer 101
87+
itA "Realise" Activity_Realise 102
88+
itA "CopyPaths" Activity_CopyPaths 103
89+
itA "Builds" Activity_Builds 104
90+
itA "Build" Activity_Build 105
91+
itA "OptimiseStore" Activity_OptimiseStore 106
92+
itA "VerifyPaths" Activity_VerifyPaths 107
93+
itA "Substitute" Activity_Substitute 108
94+
itA "QueryPathInfo" Activity_QueryPathInfo 109
95+
itA "PostBuildHook" Activity_PostBuildHook 110
96+
itA "BuildWaiting" Activity_BuildWaiting 111
97+
98+
let itR = itE' activityResult
99+
describe "ActivityResult enum order matches Nix" $ do
100+
itR "FileLinked" ActivityResult_FileLinked 100
101+
itR "BuildLogLine" ActivityResult_BuildLogLine 101
102+
itR "UnstrustedPath" ActivityResult_UnstrustedPath 102
103+
itR "CorruptedPath" ActivityResult_CorruptedPath 103
104+
itR "SetPhase" ActivityResult_SetPhase 104
105+
itR "Progress" ActivityResult_Progress 105
106+
itR "SetExpected" ActivityResult_SetExpected 106
107+
itR "PostBuildLogLine" ActivityResult_PostBuildLogLine 107
108+
109+
110+
let itL = itE' loggerOpCode
111+
describe "LoggerOpCode matches Nix" $ do
112+
itL "Next" LoggerOpCode_Next 0x6f6c6d67
113+
itL "Read" LoggerOpCode_Read 0x64617461
114+
itL "Write" LoggerOpCode_Write 0x64617416
115+
itL "Last" LoggerOpCode_Last 0x616c7473
116+
itL "Error" LoggerOpCode_Error 0x63787470
117+
itL "StartActivity" LoggerOpCode_StartActivity 0x53545254
118+
itL "StopActivity" LoggerOpCode_StopActivity 0x53544f50
119+
itL "Result" LoggerOpCode_Result 0x52534c54
120+
121+
describe "Verbosity enum order matches Nix" $ do
122+
itE "Error" Verbosity_Error 0
123+
itE "Warn" Verbosity_Warn 1
124+
itE "Notice" Verbosity_Notice 2
125+
itE "Info" Verbosity_Info 3
126+
itE "Talkative" Verbosity_Talkative 4
127+
itE "Chatty" Verbosity_Chatty 5
128+
itE "Debug" Verbosity_Debug 6
129+
itE "Vomit" Verbosity_Vomit 7
130+
131+
describe "WorkerOp enum order matches Nix" $ do
132+
itE "IsValidPath" WorkerOp_IsValidPath 1
133+
itE "BuildPathsWithResults" WorkerOp_BuildPathsWithResults 46
134+
135+
136+

hnix-store-remote/tests/NixSerializerSpec.hs

Lines changed: 1 addition & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,7 @@ module NixSerializerSpec (spec) where
55
import Crypto.Hash (MD5, SHA1, SHA256, SHA512)
66
import Data.Some (Some(Some))
77
import Data.Time (UTCTime)
8-
import Data.Word (Word64)
9-
import Test.Hspec (Expectation, Spec, describe, it, parallel, shouldBe)
8+
import Test.Hspec (Expectation, Spec, describe, parallel, shouldBe)
109
import Test.Hspec.QuickCheck (prop)
1110
import Test.QuickCheck (Gen, arbitrary, forAll, suchThat)
1211

@@ -20,7 +19,6 @@ import System.Nix.Store.Remote.Types.Logger (Logger(..))
2019
import System.Nix.Store.Remote.Types.ProtoVersion (HasProtoVersion(..), ProtoVersion(..))
2120
import System.Nix.Store.Remote.Types.StoreConfig (TestStoreConfig(..))
2221
import System.Nix.Store.Remote.Types.StoreRequest (StoreRequest(..))
23-
import System.Nix.Store.Remote.Types.WorkerOp (WorkerOp(..))
2422

2523
-- | Test for roundtrip using @NixSerializer@
2624
roundtripSReader
@@ -138,18 +136,6 @@ spec = parallel $ do
138136
forAll (arbitrary `suchThat` errorInfoIf (protoVersion_minor pv >= 26))
139137
$ roundtripSReader logger pv
140138

141-
describe "Enums" $ do
142-
let it' name constr value =
143-
it name
144-
$ (runP enum () constr)
145-
`shouldBe`
146-
(runP (int @Word64) () value)
147-
148-
describe "WorkerOp enum order matches Nix" $ do
149-
it' "IsValidPath" WorkerOp_IsValidPath 1
150-
it' "BuildPathsWithResults" WorkerOp_BuildPathsWithResults 46
151-
152-
153139
describe "Handshake" $ do
154140
prop "WorkerMagic" $ roundtripS workerMagic
155141
prop "TrustedFlag" $ roundtripS trustedFlag

hnix-store-remote/tests/SerializeSpec.hs

Lines changed: 1 addition & 76 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ import Data.Serialize (Serialize(..))
66
import Data.Serialize.Get (Get, runGet)
77
import Data.Serialize.Put (Putter, runPut)
88
import Data.Text (Text)
9-
import Test.Hspec (Expectation, Spec, describe, it, parallel, shouldBe)
9+
import Test.Hspec (Expectation, Spec, describe, parallel)
1010
import Test.Hspec.QuickCheck (prop)
1111
import Test.Hspec.Nix (roundtrips)
1212

@@ -95,78 +95,3 @@ spec = parallel $ do
9595
prop "ErrorInfo" $ roundtripS @ErrorInfo
9696
prop "LoggerOpCode" $ roundtripS @LoggerOpCode
9797
prop "Verbosity" $ roundtripS @Verbosity
98-
99-
describe "Enums" $ do
100-
let it' name constr value = it name $ runPut (put constr) `shouldBe` runPut (putInt @Int value)
101-
describe "BuildMode enum order matches Nix" $ do
102-
it' "Normal" BuildMode_Normal 0
103-
it' "Repair" BuildMode_Repair 1
104-
it' "Check" BuildMode_Check 2
105-
106-
describe "BuildStatus enum order matches Nix" $ do
107-
it' "Built" BuildStatus_Built 0
108-
it' "Substituted" BuildStatus_Substituted 1
109-
it' "AlreadyValid" BuildStatus_AlreadyValid 2
110-
it' "PermanentFailure" BuildStatus_PermanentFailure 3
111-
it' "InputRejected" BuildStatus_InputRejected 4
112-
it' "OutputRejected" BuildStatus_OutputRejected 5
113-
it' "TransientFailure" BuildStatus_TransientFailure 6
114-
it' "CachedFailure" BuildStatus_CachedFailure 7
115-
it' "TimedOut" BuildStatus_TimedOut 8
116-
it' "MiscFailure" BuildStatus_MiscFailure 9
117-
it' "DependencyFailed" BuildStatus_DependencyFailed 10
118-
it' "LogLimitExceeded" BuildStatus_LogLimitExceeded 11
119-
it' "NotDeterministic" BuildStatus_NotDeterministic 12
120-
it' "ResolvesToAlreadyValid" BuildStatus_ResolvesToAlreadyValid 13
121-
it' "NoSubstituters" BuildStatus_NoSubstituters 14
122-
123-
describe "GCAction enum order matches Nix" $ do
124-
it' "ReturnLive" GCAction_ReturnLive 0
125-
it' "ReturnDead" GCAction_ReturnDead 1
126-
it' "DeleteDead" GCAction_DeleteDead 2
127-
it' "DeleteSpecific" GCAction_DeleteSpecific 3
128-
129-
describe "Logger" $ do
130-
describe "Activity enum order matches Nix" $ do
131-
it' "CopyPath" Activity_CopyPath 100
132-
it' "FileTransfer" Activity_FileTransfer 101
133-
it' "Realise" Activity_Realise 102
134-
it' "CopyPaths" Activity_CopyPaths 103
135-
it' "Builds" Activity_Builds 104
136-
it' "Build" Activity_Build 105
137-
it' "OptimiseStore" Activity_OptimiseStore 106
138-
it' "VerifyPaths" Activity_VerifyPaths 107
139-
it' "Substitute" Activity_Substitute 108
140-
it' "QueryPathInfo" Activity_QueryPathInfo 109
141-
it' "PostBuildHook" Activity_PostBuildHook 110
142-
it' "BuildWaiting" Activity_BuildWaiting 111
143-
144-
describe "ActivityResult enum order matches Nix" $ do
145-
it' "FileLinked" ActivityResult_FileLinked 100
146-
it' "BuildLogLine" ActivityResult_BuildLogLine 101
147-
it' "UnstrustedPath" ActivityResult_UnstrustedPath 102
148-
it' "CorruptedPath" ActivityResult_CorruptedPath 103
149-
it' "SetPhase" ActivityResult_SetPhase 104
150-
it' "Progress" ActivityResult_Progress 105
151-
it' "SetExpected" ActivityResult_SetExpected 106
152-
it' "PostBuildLogLine" ActivityResult_PostBuildLogLine 107
153-
154-
describe "LoggerOpCode matches Nix" $ do
155-
it' "Next" LoggerOpCode_Next 0x6f6c6d67
156-
it' "Read" LoggerOpCode_Read 0x64617461
157-
it' "Write" LoggerOpCode_Write 0x64617416
158-
it' "Last" LoggerOpCode_Last 0x616c7473
159-
it' "Error" LoggerOpCode_Error 0x63787470
160-
it' "StartActivity" LoggerOpCode_StartActivity 0x53545254
161-
it' "StopActivity" LoggerOpCode_StopActivity 0x53544f50
162-
it' "Result" LoggerOpCode_Result 0x52534c54
163-
164-
describe "Verbosity enum order matches Nix" $ do
165-
it' "Error" Verbosity_Error 0
166-
it' "Warn" Verbosity_Warn 1
167-
it' "Notice" Verbosity_Notice 2
168-
it' "Info" Verbosity_Info 3
169-
it' "Talkative" Verbosity_Talkative 4
170-
it' "Chatty" Verbosity_Chatty 5
171-
it' "Debug" Verbosity_Debug 6
172-
it' "Vomit" Verbosity_Vomit 7

0 commit comments

Comments
 (0)