|
1 | 1 | {-# LANGUAGE NumericUnderscores #-} |
2 | 2 | module SerializeSpec where |
3 | 3 |
|
4 | | -import Prelude hiding (putText) |
| 4 | +import Data.ByteString (ByteString) |
5 | 5 | import Data.Fixed (Uni) |
| 6 | +import Data.HashSet (HashSet) |
| 7 | +import Data.Serialize (Serialize(..)) |
6 | 8 | import Data.Serialize.Get (Get, runGet) |
7 | 9 | import Data.Serialize.Put (Putter, runPut) |
8 | | -import Data.Time (NominalDiffTime, UTCTime) |
| 10 | +import Data.Text (Text) |
| 11 | +import Data.Time (NominalDiffTime) |
| 12 | +import Test.Hspec (Spec, describe, it, shouldBe) |
9 | 13 | import Test.Tasty.QuickCheck |
10 | | -import Test.QuickCheck.Instances |
11 | | - |
12 | | -import System.Nix.StorePath (StoreDir, StorePath) |
13 | | -import System.Nix.Store.Remote.Serialize |
14 | | -import System.Nix.Store.Remote.Serialize.Prim |
| 14 | +import Test.QuickCheck.Instances () |
15 | 15 |
|
| 16 | +import qualified Data.Either |
16 | 17 | import qualified Data.HashSet |
17 | 18 | import qualified Data.Time.Clock.POSIX |
| 19 | +import qualified System.Nix.Build |
| 20 | + |
| 21 | +import System.Nix.Build (BuildMode, BuildStatus, BuildResult) |
| 22 | +import System.Nix.StorePath (StoreDir, StorePath) |
| 23 | +import System.Nix.Store.Remote.Serialize () |
| 24 | +import System.Nix.Store.Remote.Serialize.Prim |
18 | 25 |
|
19 | 26 | roundTrip :: (Eq a, Show a) => Putter a -> Get a -> a -> Property |
20 | 27 | roundTrip p g a = res === Right a |
@@ -72,10 +79,52 @@ prop_path :: StoreDir -> StorePath -> Property |
72 | 79 | prop_path = \sd -> |
73 | 80 | roundTrip |
74 | 81 | (putPath sd) |
75 | | - (fromRight undefined <$> getPath sd) |
| 82 | + (Data.Either.fromRight undefined <$> getPath sd) |
76 | 83 |
|
77 | 84 | prop_paths :: StoreDir -> HashSet StorePath -> Property |
78 | 85 | prop_paths = \sd -> |
79 | 86 | roundTrip |
80 | 87 | (putPaths sd) |
81 | | - (Data.HashSet.map (fromRight undefined) <$> getPaths sd) |
| 88 | + (Data.HashSet.map (Data.Either.fromRight undefined) <$> getPaths sd) |
| 89 | + |
| 90 | +-- * Serialize |
| 91 | +roundTripS :: (Eq a, Serialize a, Show a) => a -> Property |
| 92 | +roundTripS a = res === Right a |
| 93 | + where res = runGet get (runPut (put a)) |
| 94 | + |
| 95 | +-- ** Text |
| 96 | + |
| 97 | +prop_Text :: Text -> Property |
| 98 | +prop_Text = roundTripS |
| 99 | + |
| 100 | +-- ** BuildMode |
| 101 | + |
| 102 | +prop_buildMode :: BuildMode -> Property |
| 103 | +prop_buildMode = roundTripS |
| 104 | + |
| 105 | +prop_buildStatus :: BuildStatus -> Property |
| 106 | +prop_buildStatus = roundTripS |
| 107 | + |
| 108 | +spec_buildMode :: Spec |
| 109 | +spec_buildMode = |
| 110 | + let it' name constr value = it name $ runPut (put constr) `shouldBe` runPut (putInt value) |
| 111 | + in do |
| 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 |
0 commit comments