hnix-store-remote-0.7.0.0: Remote hnix store
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Nix.Store.Remote.Types.StoreRequest

Documentation

data StoreRequest :: Type -> Type where Source #

Constructors

AddToStore

Add NarSource to the store.

Fields

AddToStoreNar

Add a NAR with Metadata to the store.

Fields

AddTextToStore

Add text to store.

Reference accepts repair but only uses it to throw error in case of remote talking to nix-daemon.

Fields

AddSignatures :: StorePath -> Set Signature -> StoreRequest SuccessCodeReply 
AddIndirectRoot :: StorePath -> StoreRequest SuccessCodeReply 
AddTempRoot :: StorePath -> StoreRequest SuccessCodeReply

Add temporary garbage collector root.

This root is removed as soon as the client exits.

BuildPaths :: Set DerivedPath -> BuildMode -> StoreRequest SuccessCodeReply

Build paths if they are an actual derivations.

If derivation output paths are already valid, do nothing.

BuildDerivation :: StorePath -> Derivation StorePath Text -> BuildMode -> StoreRequest BuildResult 
CollectGarbage :: GCOptions -> StoreRequest GCResult 
EnsurePath :: StorePath -> StoreRequest SuccessCodeReply 
FindRoots :: StoreRequest (Map GCRoot StorePath)

Find garbage collector roots.

IsValidPath :: StorePath -> StoreRequest Bool 
NarFromPath :: StorePath -> StoreRequest NoReply

Fetch a NAR from the server

QueryValidPaths

Query valid paths from set, optionally try to use substitutes.

Fields

QueryAllValidPaths :: StoreRequest (HashSet StorePath) 
QuerySubstitutablePaths :: HashSet StorePath -> StoreRequest (HashSet StorePath) 
QueryPathInfo :: StorePath -> StoreRequest (Maybe (Metadata StorePath)) 
QueryReferrers :: StorePath -> StoreRequest (HashSet StorePath) 
QueryValidDerivers :: StorePath -> StoreRequest (HashSet StorePath) 
QueryDerivationOutputs :: StorePath -> StoreRequest (HashSet StorePath) 
QueryDerivationOutputNames :: StorePath -> StoreRequest (HashSet StorePathName) 
QueryPathFromHashPart :: StorePathHashPart -> StoreRequest StorePath 
QueryMissing :: Set DerivedPath -> StoreRequest Missing 
OptimiseStore :: StoreRequest SuccessCodeReply 
SyncWithGC :: StoreRequest SuccessCodeReply 
VerifyStore :: CheckMode -> RepairMode -> StoreRequest Bool 

Instances

Instances details
GCompare StoreRequest Source # 
Instance details

Defined in System.Nix.Store.Remote.Types.StoreRequest

Methods

gcompare :: forall (a :: k) (b :: k). StoreRequest a -> StoreRequest b -> GOrdering a b #

GEq StoreRequest Source # 
Instance details

Defined in System.Nix.Store.Remote.Types.StoreRequest

Methods

geq :: forall (a :: k) (b :: k). StoreRequest a -> StoreRequest b -> Maybe (a :~: b) #

GShow StoreRequest Source # 
Instance details

Defined in System.Nix.Store.Remote.Types.StoreRequest

Methods

gshowsPrec :: forall (a :: k). Int -> StoreRequest a -> ShowS #

Show (StoreRequest a) Source # 
Instance details

Defined in System.Nix.Store.Remote.Types.StoreRequest

Eq (StoreRequest a) Source # 
Instance details

Defined in System.Nix.Store.Remote.Types.StoreRequest

Arbitrary (Some StoreRequest) Source # 
Instance details

Defined in System.Nix.Store.Remote.Arbitrary

Eq (Some StoreRequest) Source # 
Instance details

Defined in System.Nix.Store.Remote.Types.StoreRequest