Skip to content

Commit

Permalink
Convert StorePathMetadata into Metadata a
Browse files Browse the repository at this point in the history
Also derive bunch of common instances.

Closes #147
  • Loading branch information
sorki committed Nov 16, 2023
1 parent a75162d commit e6f016d
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 17 deletions.
1 change: 1 addition & 0 deletions hnix-store-core/CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
# Next

* Changes:
* `StorePathMetadata` converted to `Metadata a` [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* Constructors of `StorePathName` and `StorePathHashPart` are no longer
exported. Use respective `mkStorePath..` functions. [#230](https://github.com/haskell-nix/hnix-store/pull/230)
* `StorePathSet` type alias is no more, use `HashSet StorePath` [#230](https://github.com/haskell-nix/hnix-store/pull/230)
Expand Down
30 changes: 16 additions & 14 deletions hnix-store-core/src/System/Nix/StorePathMetadata.hs
Original file line number Diff line number Diff line change
@@ -1,27 +1,29 @@
{-|
Description : Metadata about Nix store paths.
-}
module System.Nix.StorePathMetadata where
module System.Nix.StorePathMetadata
( Metadata(..)
, StorePathTrust(..)
) where

import System.Nix.StorePath ( StorePath
, ContentAddressableAddress
)
import System.Nix.Hash ( SomeNamedDigest )
import Data.Time ( UTCTime )
import System.Nix.Signature ( NarSignature )
import Data.Time (UTCTime)

-- | Metadata about a 'StorePath'
data StorePathMetadata = StorePathMetadata
import System.Nix.Hash (SomeNamedDigest)
import System.Nix.Signature (NarSignature)
import System.Nix.StorePath (ContentAddressableAddress)

-- | Metadata (typically about a 'StorePath')
data Metadata a = Metadata
{ -- | The path this metadata is about
path :: !StorePath
path :: !a
, -- | The path to the derivation file that built this path, if any
-- and known.
deriverPath :: !(Maybe StorePath)
deriverPath :: !(Maybe a)
, -- TODO should this be optional?
-- | The hash of the nar serialization of the path.
narHash :: !SomeNamedDigest
, -- | The paths that this path directly references
references :: !(HashSet StorePath)
references :: !(HashSet a)
, -- | When was this path registered valid in the store?
registrationTime :: !UTCTime
, -- | The size of the nar serialization of the path, in bytes.
Expand All @@ -38,7 +40,7 @@ data StorePathMetadata = StorePathMetadata
-- There is no guarantee from this type alone that this address
-- is actually correct for this store path.
contentAddressableAddress :: !(Maybe ContentAddressableAddress)
}
} deriving (Eq, Generic, Ord, Show)

-- | How much do we trust the path, based on its provenance?
data StorePathTrust
Expand All @@ -47,4 +49,4 @@ data StorePathTrust
| -- | It was built elsewhere (and substituted or similar) and so
-- is less trusted
BuiltElsewhere
deriving (Show, Eq, Ord)
deriving (Eq, Enum, Generic, Ord, Show)
6 changes: 3 additions & 3 deletions hnix-store-remote/src/System/Nix/Store/Remote.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ import System.Nix.StorePath ( StorePath
, StorePathHashPart
, InvalidPathError
)
import System.Nix.StorePathMetadata ( StorePathMetadata(..)
import System.Nix.StorePathMetadata ( Metadata(..)
, StorePathTrust(..)
)
import System.Nix.Internal.Base ( encodeWith )
Expand Down Expand Up @@ -225,7 +225,7 @@ querySubstitutablePaths ps = do
runOpArgs QuerySubstitutablePaths $ putPaths storeDir ps
sockGetPaths

queryPathInfoUncached :: StorePath -> MonadStore StorePathMetadata
queryPathInfoUncached :: StorePath -> MonadStore (Metadata StorePath)
queryPathInfoUncached path = do
storeDir <- getStoreDir
runOpArgs QueryPathInfo $ do
Expand Down Expand Up @@ -266,7 +266,7 @@ queryPathInfoUncached path = do

trust = if ultimate then BuiltLocally else BuiltElsewhere

pure $ StorePathMetadata{..}
pure $ Metadata{..}

queryReferrers :: StorePath -> MonadStore (HashSet StorePath)
queryReferrers p = do
Expand Down

0 comments on commit e6f016d

Please sign in to comment.