hnix-store-core-0.8.0.0: Core types used for interacting with the Nix store.
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Nix.StorePath

Description

 
Synopsis

Basic store path types

newtype StoreDir Source #

The path to the store dir

Many operations need to be parameterized with this, since store paths do not know their own store dir by design.

Constructors

StoreDir 

Fields

Instances

Instances details
Generic StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

Associated Types

type Rep StoreDir :: Type -> Type #

Methods

from :: StoreDir -> Rep StoreDir x #

to :: Rep StoreDir x -> StoreDir #

Show StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

Default StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

Methods

def :: StoreDir #

Eq StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

Ord StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

Hashable StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

Methods

hashWithSalt :: Int -> StoreDir -> Int #

hash :: StoreDir -> Int #

type Rep StoreDir Source # 
Instance details

Defined in System.Nix.StorePath

class HasStoreDir r where Source #

Methods

hasStoreDir :: r -> StoreDir Source #

data StorePath Source #

A path in a Nix store.

From the Nix thesis: A store path is the full path of a store object. It has the following anatomy: storeDir/hashPart-name.

The store directory is *not* included, and must be known from the context. This matches modern C++ Nix, and also represents the fact that store paths for different store directories cannot be mixed.

Instances

Instances details
Generic StorePath Source # 
Instance details

Defined in System.Nix.StorePath

Associated Types

type Rep StorePath :: Type -> Type #

Show StorePath Source # 
Instance details

Defined in System.Nix.StorePath

Eq StorePath Source # 
Instance details

Defined in System.Nix.StorePath

Ord StorePath Source # 
Instance details

Defined in System.Nix.StorePath

Hashable StorePath Source # 
Instance details

Defined in System.Nix.StorePath

type Rep StorePath Source # 
Instance details

Defined in System.Nix.StorePath

type Rep StorePath = D1 ('MetaData "StorePath" "System.Nix.StorePath" "hnix-store-core-0.8.0.0-2YQUX8JlMxk93e1fw1Y66G" 'False) (C1 ('MetaCons "StorePath" 'PrefixI 'True) (S1 ('MetaSel ('Just "storePathHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StorePathHashPart) :*: S1 ('MetaSel ('Just "storePathName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StorePathName)))

storePathHash :: StorePath -> StorePathHashPart Source #

The 160-bit hash digest reflecting the "address" of the name. Currently, this is a truncated SHA256 hash.

storePathName :: StorePath -> StorePathName Source #

The (typically human readable) name of the path. For packages this is typically the package name and version (e.g. hello-1.2.3).

data StorePathName Source #

The name portion of a Nix path.

unStorePathName must only contain a-zA-Z0-9+._?=-, can't start with a -, and must have at least one character (i.e. it must match storePathNameRegex).

Instances

Instances details
Generic StorePathName Source # 
Instance details

Defined in System.Nix.StorePath

Associated Types

type Rep StorePathName :: Type -> Type #

Show StorePathName Source # 
Instance details

Defined in System.Nix.StorePath

Eq StorePathName Source # 
Instance details

Defined in System.Nix.StorePath

Ord StorePathName Source # 
Instance details

Defined in System.Nix.StorePath

Hashable StorePathName Source # 
Instance details

Defined in System.Nix.StorePath

type Rep StorePathName Source # 
Instance details

Defined in System.Nix.StorePath

type Rep StorePathName = D1 ('MetaData "StorePathName" "System.Nix.StorePath" "hnix-store-core-0.8.0.0-2YQUX8JlMxk93e1fw1Y66G" 'True) (C1 ('MetaCons "StorePathName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStorePathName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

unStorePathName :: StorePathName -> Text Source #

Extract the contents of the name.

data StorePathHashPart Source #

The hash algorithm used for store path hashes.

Instances

Instances details
Generic StorePathHashPart Source # 
Instance details

Defined in System.Nix.StorePath

Associated Types

type Rep StorePathHashPart :: Type -> Type #

Show StorePathHashPart Source # 
Instance details

Defined in System.Nix.StorePath

Eq StorePathHashPart Source # 
Instance details

Defined in System.Nix.StorePath

Ord StorePathHashPart Source # 
Instance details

Defined in System.Nix.StorePath

Hashable StorePathHashPart Source # 
Instance details

Defined in System.Nix.StorePath

type Rep StorePathHashPart Source # 
Instance details

Defined in System.Nix.StorePath

type Rep StorePathHashPart = D1 ('MetaData "StorePathHashPart" "System.Nix.StorePath" "hnix-store-core-0.8.0.0-2YQUX8JlMxk93e1fw1Y66G" 'True) (C1 ('MetaCons "StorePathHashPart" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStorePathHashPart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

mkStorePathHashPart :: forall hashAlgo. HashAlgorithm hashAlgo => ByteString -> StorePathHashPart Source #

Make StorePathHashPart from ByteString (hash part of the StorePath) using specific HashAlgorithm

unStorePathHashPart :: StorePathHashPart -> ByteString Source #

Extract the contents of the hash.

Manipulating StorePathName

data InvalidNameError Source #

Reason why a path name or output name is not valid

Instances

Instances details
Generic InvalidNameError Source # 
Instance details

Defined in System.Nix.StorePath

Associated Types

type Rep InvalidNameError :: Type -> Type #

Show InvalidNameError Source # 
Instance details

Defined in System.Nix.StorePath

Eq InvalidNameError Source # 
Instance details

Defined in System.Nix.StorePath

Ord InvalidNameError Source # 
Instance details

Defined in System.Nix.StorePath

Hashable InvalidNameError Source # 
Instance details

Defined in System.Nix.StorePath

type Rep InvalidNameError Source # 
Instance details

Defined in System.Nix.StorePath

type Rep InvalidNameError = D1 ('MetaData "InvalidNameError" "System.Nix.StorePath" "hnix-store-core-0.8.0.0-2YQUX8JlMxk93e1fw1Y66G" 'False) ((C1 ('MetaCons "EmptyName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NameTooLong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "LeadingDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvalidCharacters" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

mkStorePathName :: Text -> Either InvalidNameError StorePathName Source #

Make StorePathName from Text (name part of the StorePath) or fail with InvalidNameError if it isn't valid

parseNameText :: Text -> Either InvalidNameError Text Source #

Parse name (either StorePathName or OutputName)

Reason why a path is not valid

data InvalidPathError Source #

Reason why a path is not valid

Instances

Instances details
Generic InvalidPathError Source # 
Instance details

Defined in System.Nix.StorePath

Associated Types

type Rep InvalidPathError :: Type -> Type #

Show InvalidPathError Source # 
Instance details

Defined in System.Nix.StorePath

Eq InvalidPathError Source # 
Instance details

Defined in System.Nix.StorePath

Ord InvalidPathError Source # 
Instance details

Defined in System.Nix.StorePath

Hashable InvalidPathError Source # 
Instance details

Defined in System.Nix.StorePath

type Rep InvalidPathError Source # 
Instance details

Defined in System.Nix.StorePath

type Rep InvalidPathError = D1 ('MetaData "InvalidPathError" "System.Nix.StorePath" "hnix-store-core-0.8.0.0-2YQUX8JlMxk93e1fw1Y66G" 'False) (C1 ('MetaCons "PathNameInvalid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InvalidNameError)) :+: (C1 ('MetaCons "HashDecodingFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "RootDirMismatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "rdMismatchExpected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StoreDir) :*: S1 ('MetaSel ('Just "rdMismatchGot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StoreDir))))

Rendering out StorePaths

storePathToRawFilePath :: StoreDir -> StorePath -> RawFilePath Source #

Render a StorePath as a RawFilePath.

storePathToNarInfo :: StorePath -> ByteString Source #

Build narinfo suffix from StorePath which can be used to query binary caches.

storePathHashPartToText :: StorePathHashPart -> Text Source #

Render a StorePathHashPart as a Text. This is used by remote store / database via queryPathFromHashPart

Parsing StorePaths

parsePath Source #

Arguments

:: StoreDir

expected StoreDir

-> ByteString 
-> Either InvalidPathError StorePath 

Parse StorePath from ByteString, checking that store directory matches expectedRoot.

parsePathFromText Source #

Arguments

:: StoreDir

expected StoreDir

-> Text 
-> Either InvalidPathError StorePath 

Parse StorePath from Text, checking that store directory matches expectedRoot.

pathParser :: StoreDir -> Parser StorePath Source #

Attoparsec StorePath Parser

Utilities for tests

unsafeMakeStorePath :: StorePathHashPart -> StorePathName -> StorePath Source #

Paths rarely need to be constructed directly. Prefer parsePath or parsePathFromText

unsafeMakeStorePathHashPart :: ByteString -> StorePathHashPart Source #

Path hash parts rarely need to be constructed directly. Prefer mkStorePathHashPart Used by remote store in wire protocol