Skip to content

Commit

Permalink
hnix-store-remote: implement buildPaths op
Browse files Browse the repository at this point in the history
I was hoping to use the `StorePath` type from `System.Nix.StorePath`,
but I am not sure how to construct its values at runtime. I ended up
giving `buildPaths` a simpler type that expects a list of bytestrings.
  • Loading branch information
stolyaroleh committed Aug 26, 2019
1 parent 1e85a50 commit cee9c9c
Showing 1 changed file with 27 additions and 3 deletions.
30 changes: 27 additions & 3 deletions hnix-store-remote/src/System/Nix/Store/Remote.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,17 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module System.Nix.Store.Remote (
runStore
BuildMode(..)
, runStore
, syncWithGC
, optimiseStore
, verifyStore
, buildPaths
) where

import Control.Monad

import Data.Binary.Put (Put, putInthost)
import Data.ByteString (ByteString)
import System.Nix.Util
import System.Nix.Store.Remote.Types
import System.Nix.Store.Remote.Protocol
import System.Nix.Store.Remote.Util
Expand All @@ -31,3 +34,24 @@ verifyStore :: CheckFlag -> RepairFlag -> MonadStore ()
verifyStore check repair = runOpArgs_ VerifyStore $ do
putBool check
putBool repair

data BuildMode = Normal | Repair | Check
deriving (Eq, Show)

putBuildMode :: BuildMode -> Put
putBuildMode mode = putInthost $
case mode of
Normal -> 0
Repair -> 1
Check -> 2

buildPaths ::
-- forall storeDir . (KnownStoreDir storeDir) =>
-- [StorePath storeDir]
[ByteString] -> BuildMode -> MonadStore ()
buildPaths drvs mode =
runOpArgs_ BuildPaths args
where
args = do
putByteStrings drvs
putBuildMode mode

0 comments on commit cee9c9c

Please sign in to comment.