11-- | Stream out a NAR file from a regular file
22
3- {-# language ScopedTypeVariables #-}
3+ {-# LANGUAGE ScopedTypeVariables #-}
44
55module System.Nix.Internal.Nar.Streamer
66 ( NarSource
@@ -16,8 +16,10 @@ import qualified Data.ByteString as Bytes
1616import qualified Data.ByteString.Char8 as Bytes.Char8
1717import qualified Data.ByteString.Lazy as Bytes.Lazy
1818import qualified Data.Serialize as Serial
19+ import qualified Data.Text as T (pack )
20+ import qualified Data.Text.Encoding as TE (encodeUtf8 )
1921import qualified System.Directory as Directory
20- import System.FilePath ( (</>) )
22+ import System.FilePath ( (</>) )
2123
2224import qualified System.Nix.Internal.Nar.Effects as Nar
2325
@@ -61,33 +63,32 @@ streamNarIO effs basePath yield = do
6163 where
6264 go :: FilePath -> m ()
6365 go path = do
64- isDir <- IO. liftIO $ Nar. narIsDir effs path
6566 isSymLink <- IO. liftIO $ Nar. narIsSymLink effs path
66- let isRegular = not $ isDir || isSymLink
67-
68- when isSymLink $ do
67+ if isSymLink then do
6968 target <- IO. liftIO $ Nar. narReadLink effs path
7069 yield $
71- strs [" type" , " symlink" , " target" , Bytes.Char8. pack target]
72-
73- when isRegular $ do
74- isExec <- IO. liftIO $ isExecutable effs path
75- yield $ strs [" type" , " regular" ]
76- when (isExec == Executable ) $ yield $ strs [" executable" , " " ]
77- fSize <- IO. liftIO $ Nar. narFileSize effs path
78- yield $ str " contents"
79- yield $ int fSize
80- yieldFile path fSize
81-
82- when (isDir && not isSymLink) $ do
83- fs <- IO. liftIO (Nar. narListDir effs path)
84- yield $ strs [" type" , " directory" ]
85- forM_ (sort fs) $ \ f -> do
86- yield $ str " entry"
87- parens $ do
88- let fullName = path </> f
89- yield $ strs [" name" , Bytes.Char8. pack f, " node" ]
90- parens $ go fullName
70+ strs [" type" , " symlink" , " target" , filePathToBS target]
71+ else do
72+ isDir <- IO. liftIO $ Nar. narIsDir effs path
73+ if isDir then do
74+ fs <- IO. liftIO (Nar. narListDir effs path)
75+ yield $ strs [" type" , " directory" ]
76+ forM_ (sort fs) $ \ f -> do
77+ yield $ str " entry"
78+ parens $ do
79+ let fullName = path </> f
80+ yield $ strs [" name" , filePathToBS f, " node" ]
81+ parens $ go fullName
82+ else do
83+ isExec <- IO. liftIO $ isExecutable effs path
84+ yield $ strs [" type" , " regular" ]
85+ when (isExec == Executable ) $ yield $ strs [" executable" , " " ]
86+ fSize <- IO. liftIO $ Nar. narFileSize effs path
87+ yield $ str " contents"
88+ yield $ int fSize
89+ yieldFile path fSize
90+
91+ filePathToBS = TE. encodeUtf8 . T. pack
9192
9293 parens act = do
9394 yield $ str " ("
0 commit comments