Safe Haskell | None |
---|---|
Language | Haskell2010 |
NixTree.StorePath
Documentation
Instances
Generic StoreName Source # | |
Show StoreName Source # | |
NFData StoreName Source # | |
Defined in NixTree.StorePath | |
Eq StoreName Source # | |
Ord StoreName Source # | |
Hashable StoreName Source # | |
Defined in NixTree.StorePath | |
type Rep StoreName Source # | |
Defined in NixTree.StorePath |
storeNameToPath :: StoreName -> FilePath Source #
storeNameToText :: StoreName -> Text Source #
storeNameToShortText :: StoreName -> Text Source #
data NixPathSignature Source #
Constructors
NixPathSignature | |
Fields
|
Instances
data StorePath ref payload Source #
Constructors
StorePath | |
Fields
|
Instances
Functor (StorePath ref) Source # | |||||
Generic (StorePath ref payload) Source # | |||||
Defined in NixTree.StorePath Associated Types
| |||||
(Show ref, Show payload) => Show (StorePath ref payload) Source # | |||||
(NFData a, NFData b) => NFData (StorePath a b) Source # | |||||
Defined in NixTree.StorePath | |||||
(Eq ref, Eq payload) => Eq (StorePath ref payload) Source # | |||||
(Ord ref, Ord payload) => Ord (StorePath ref payload) Source # | |||||
Defined in NixTree.StorePath Methods compare :: StorePath ref payload -> StorePath ref payload -> Ordering # (<) :: StorePath ref payload -> StorePath ref payload -> Bool # (<=) :: StorePath ref payload -> StorePath ref payload -> Bool # (>) :: StorePath ref payload -> StorePath ref payload -> Bool # (>=) :: StorePath ref payload -> StorePath ref payload -> Bool # max :: StorePath ref payload -> StorePath ref payload -> StorePath ref payload # min :: StorePath ref payload -> StorePath ref payload -> StorePath ref payload # | |||||
type Rep (StorePath ref payload) Source # | |||||
Defined in NixTree.StorePath type Rep (StorePath ref payload) = D1 ('MetaData "StorePath" "NixTree.StorePath" "nix-tree-0.7.0-HNPzNedb4REJMzrrj53EmD" 'False) (C1 ('MetaCons "StorePath" 'PrefixI 'True) ((S1 ('MetaSel ('Just "spName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StoreName) :*: S1 ('MetaSel ('Just "spSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "spRefs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ref]) :*: (S1 ('MetaSel ('Just "spPayload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 payload) :*: S1 ('MetaSel ('Just "spSignatures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NixPathSignature]))))) |
newtype Installable Source #
Constructors
Installable | |
Fields |
data StoreEnv payload Source #
Constructors
StoreEnv | |
Instances
Functor StoreEnv Source # | |||||
Generic (StoreEnv payload) Source # | |||||
Defined in NixTree.StorePath Associated Types
| |||||
NFData payload => NFData (StoreEnv payload) Source # | |||||
Defined in NixTree.StorePath | |||||
type Rep (StoreEnv payload) Source # | |||||
Defined in NixTree.StorePath type Rep (StoreEnv payload) = D1 ('MetaData "StoreEnv" "NixTree.StorePath" "nix-tree-0.7.0-HNPzNedb4REJMzrrj53EmD" 'False) (C1 ('MetaCons "StoreEnv" 'PrefixI 'True) (S1 ('MetaSel ('Just "sePaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap StoreName (StorePath StoreName payload))) :*: S1 ('MetaSel ('Just "seRoots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty StoreName)))) |
data StoreEnvOptions Source #
Constructors
StoreEnvOptions | |
Fields
|
withStoreEnv :: MonadIO m => StoreEnvOptions -> NonEmpty Installable -> (StoreEnv () -> m a) -> m a Source #
seBottomUp :: forall a b. (StorePath (StorePath StoreName b) a -> b) -> StoreEnv a -> StoreEnv b Source #
seFetchRefs :: StoreEnv a -> (StoreName -> Bool) -> NonEmpty StoreName -> [StorePath StoreName a] Source #
storeEnvToDot :: StoreEnv a -> Text Source #