77{-# LANGUAGE MultiParamTypeClasses #-}
88{-# LANGUAGE OverloadedStrings #-}
99{-# LANGUAGE TypeFamilies #-}
10+ {-# LANGUAGE DataKinds #-}
11+ {-# LANGUAGE TypeApplications #-}
1012
1113module Nix.Effects where
1214
@@ -17,24 +19,31 @@ import Prelude hiding ( putStr
1719import qualified Prelude
1820
1921import Control.Monad.Trans
22+ import qualified Data.HashSet as HS
2023import Data.Text ( Text )
2124import qualified Data.Text as T
22- import Network.HTTP.Client hiding ( path )
25+ import qualified Data.Text.Encoding as T
26+ import Network.HTTP.Client hiding ( path , Proxy )
2327import Network.HTTP.Client.TLS
2428import Network.HTTP.Types
2529import Nix.Expr
26- import Nix.Frames
30+ import Nix.Frames hiding ( Proxy )
2731import Nix.Parser
2832import Nix.Render
2933import Nix.Utils
3034import Nix.Value
3135import qualified Paths_hnix
32- import qualified System.Directory as S
3336import System.Environment
3437import System.Exit
38+ import System.FilePath ( takeFileName )
3539import qualified System.Info
3640import System.Process
3741
42+ import qualified System.Nix.Hash as Store
43+ import qualified System.Nix.Store.Remote as Store
44+ import qualified System.Nix.Store.Remote.Types as Store
45+ import qualified System.Nix.StorePath as Store
46+
3847-- | A path into the nix store
3948newtype StorePath = StorePath { unStorePath :: FilePath }
4049
@@ -226,36 +235,55 @@ print = putStrLn . show
226235instance MonadPutStr IO where
227236 putStr = Prelude. putStr
228237
238+
239+ type RecursiveFlag = Bool
240+ type RepairFlag = Bool
241+ type StorePathName = Text
242+ type FilePathFilter m = FilePath -> m Bool
243+ type StorePathSet = HS. HashSet StorePath
244+
229245class Monad m => MonadStore m where
230- -- | Import a path into the nix store, and return the resulting path
231- addPath' :: FilePath -> m (Either ErrorCall StorePath )
232246
233- -- | Add a file with the given name and contents to the nix store
234- toFile_' :: FilePath -> String -> m (Either ErrorCall StorePath )
247+ -- | Copy the contents of a local path to the store. The resulting store
248+ -- path is returned. Note: This does not support yet support the expected
249+ -- `filter` function that allows excluding some files.
250+ addToStore :: StorePathName -> FilePath -> RecursiveFlag -> RepairFlag -> m (Either ErrorCall StorePath )
251+ default addToStore :: (MonadTrans t , MonadStore m' , m ~ t m' ) => StorePathName -> FilePath -> RecursiveFlag -> RepairFlag -> m (Either ErrorCall StorePath )
252+ addToStore a b c d = lift $ addToStore a b c d
253+
254+ -- | Like addToStore, but the contents written to the output path is a
255+ -- regular file containing the given string.
256+ addTextToStore' :: StorePathName -> Text -> Store. StorePathSet -> RepairFlag -> m (Either ErrorCall StorePath )
257+ default addTextToStore' :: (MonadTrans t , MonadStore m' , m ~ t m' ) => StorePathName -> Text -> Store. StorePathSet -> RepairFlag -> m (Either ErrorCall StorePath )
258+ addTextToStore' a b c d = lift $ addTextToStore' a b c d
259+
260+ parseStoreResult :: Monad m => String -> (Either String a , [Store. Logger ]) -> m (Either ErrorCall a )
261+ parseStoreResult name res = case res of
262+ (Left msg, logs) -> return $ Left $ ErrorCall $ " Failed to execute '" ++ name ++ " ': " ++ msg ++ " \n " ++ show logs
263+ (Right result, _) -> return $ Right result
235264
236265instance MonadStore IO where
237- addPath' path = do
238- (exitCode, out, _) <- readProcessWithExitCode " nix-store" [" --add" , path] " "
239- case exitCode of
240- ExitSuccess -> do
241- let dropTrailingLinefeed p = take (length p - 1 ) p
242- pure $ Right $ StorePath $ dropTrailingLinefeed out
243- _ ->
244- pure
245- $ Left
246- $ ErrorCall
247- $ " addPath: failed: nix-store --add "
248- ++ show path
249266
250- -- TODO: Use a temp directory so we don't overwrite anything important
251- toFile_' filepath content = do
252- writeFile filepath content
253- storepath <- addPath' filepath
254- S. removeFile filepath
255- pure storepath
267+ addToStore name path recursive repair = case Store. makeStorePathName name of
268+ Left err -> return $ Left $ ErrorCall $ " String '" ++ show name ++ " ' is not a valid path name: " ++ err
269+ Right pathName -> do
270+ -- TODO: redesign the filter parameter
271+ res <- Store. runStore $ Store. addToStore @ 'Store.SHA256 pathName path recursive (const False ) repair
272+ parseStoreResult " addToStore" res >>= \ case
273+ Left err -> return $ Left err
274+ Right storePath -> return $ Right $ StorePath $ T. unpack $ T. decodeUtf8 $ Store. storePathToRawFilePath storePath
275+
276+ addTextToStore' name text references repair = do
277+ res <- Store. runStore $ Store. addTextToStore name text references repair
278+ parseStoreResult " addTextToStore" res >>= \ case
279+ Left err -> return $ Left err
280+ Right path -> return $ Right $ StorePath $ T. unpack $ T. decodeUtf8 $ Store. storePathToRawFilePath path
281+
282+ addTextToStore :: (Framed e m , MonadStore m ) => StorePathName -> Text -> Store. StorePathSet -> RepairFlag -> m StorePath
283+ addTextToStore a b c d = either throwError return =<< addTextToStore' a b c d
256284
257285addPath :: (Framed e m , MonadStore m ) => FilePath -> m StorePath
258- addPath p = either throwError pure =<< addPath' p
286+ addPath p = either throwError return =<< addToStore ( T. pack $ takeFileName p) p True False
259287
260288toFile_ :: (Framed e m , MonadStore m ) => FilePath -> String -> m StorePath
261- toFile_ p contents = either throwError pure =<< toFile_' p contents
289+ toFile_ p contents = addTextToStore ( T. pack p) ( T. pack contents) HS. empty False
0 commit comments