ReadonlyStore: Update to use new StorePath module.

This commit is contained in:
Shea Levy 2019-03-22 09:21:30 -04:00
parent aabde18a4a
commit 8fa011942e
No known key found for this signature in database
GPG Key ID: 5C0BD6957D86FE27
3 changed files with 29 additions and 21 deletions

View File

@ -7,6 +7,9 @@ Description : Representation of Nix store paths.
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
module System.Nix.Internal.StorePath where
import System.Nix.Hash (HashAlgorithm(Truncated, SHA256), Digest, encodeBase32)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
@ -19,6 +22,7 @@ import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BC
import Data.Hashable (Hashable(..))
import Data.HashSet (HashSet)
import Data.Proxy (Proxy(..))
-- | A path in a Nix store.
--
@ -132,10 +136,10 @@ type RawFilePath = ByteString
-- | Render a 'StorePath' as a 'RawFilePath'.
storePathToRawFilePath
:: (KnownStoreDir storeDir)
:: forall storeDir . (KnownStoreDir storeDir)
=> StorePath storeDir
-> RawFilePath
storePathToRawFilePath s@(StorePath {..}) = BS.concat
storePathToRawFilePath (StorePath {..}) = BS.concat
[ root
, "/"
, hashPart
@ -143,9 +147,14 @@ storePathToRawFilePath s@(StorePath {..}) = BS.concat
, name
]
where
root = BC.pack $ symbolVal s
root = storeDirVal @storeDir
hashPart = encodeUtf8 $ encodeBase32 storePathHash
name = encodeUtf8 $ unStorePathName storePathName
-- | Get a value-level representation of a 'KnownStoreDir'
storeDirVal :: forall storeDir . (KnownStoreDir storeDir)
=> ByteString
storeDirVal = BC.pack $ symbolVal @storeDir Proxy
-- | A 'StoreDir' whose value is known at compile time.
type KnownStoreDir = KnownSymbol

View File

@ -1,34 +1,32 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
module System.Nix.ReadonlyStore where
import Data.ByteString (ByteString)
import Data.ByteString.Base16 as Base16
import qualified Data.ByteString as BS
import qualified Data.HashSet as HS
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Encoding
import System.Nix.Hash
import System.Nix.Path
import System.Nix.StorePath
makeStorePath :: Text -> Text -> Digest 'SHA256 -> Text -> Path
makeStorePath storeDir ty h nm = Path storeHash (PathName nm)
makeStorePath :: forall storeDir . (KnownStoreDir storeDir) => ByteString -> Digest 'SHA256 -> StorePathName -> StorePath storeDir
makeStorePath ty h nm = StorePath storeHash nm
where
s = T.intercalate ":"
s = BS.intercalate ":"
[ ty
, algoName @'SHA256
, encodeBase16 h
, storeDir
, nm
, encodeUtf8 $ algoName @'SHA256
, encodeUtf8 $ encodeBase16 h
, storeDirVal @storeDir
, encodeUtf8 $ unStorePathName nm
]
storeHash = hash $ encodeUtf8 s
storeHash = hash s
makeTextPath :: Text -> Text -> Digest 'SHA256 -> PathSet -> Path
makeTextPath storeDir nm h refs = makeStorePath storeDir ty h nm
makeTextPath :: (KnownStoreDir storeDir) => StorePathName -> Digest 'SHA256 -> StorePathSet storeDir -> StorePath storeDir
makeTextPath nm h refs = makeStorePath ty h nm
where
ty = T.intercalate ":" ("text" : map (pathToText storeDir) (HS.toList refs))
ty = BS.intercalate ":" ("text" : map storePathToRawFilePath (HS.toList refs))
computeStorePathForText :: Text -> Text -> ByteString -> PathSet -> Path
computeStorePathForText storeDir nm s refs = makeTextPath storeDir nm (hash s) refs
computeStorePathForText :: (KnownStoreDir storeDir) => StorePathName -> ByteString -> StorePathSet storeDir -> StorePath storeDir
computeStorePathForText nm s refs = makeTextPath nm (hash s) refs

View File

@ -14,6 +14,7 @@ module System.Nix.StorePath
, storePathNameRegex
, -- * Rendering out 'StorePath's
storePathToRawFilePath
, storeDirVal
, KnownStoreDir
) where