nix-tree-0.7.0: Interactively browse a Nix store paths dependencies
Safe HaskellNone
LanguageHaskell2010

NixTree.StorePath

Documentation

data StoreName Source #

Constructors

StoreName NixStore Text 

Instances

Instances details
Generic StoreName Source # 
Instance details

Defined in NixTree.StorePath

Associated Types

type Rep StoreName 
Instance details

Defined in NixTree.StorePath

Show StoreName Source # 
Instance details

Defined in NixTree.StorePath

NFData StoreName Source # 
Instance details

Defined in NixTree.StorePath

Methods

rnf :: StoreName -> () #

Eq StoreName Source # 
Instance details

Defined in NixTree.StorePath

Ord StoreName Source # 
Instance details

Defined in NixTree.StorePath

Hashable StoreName Source # 
Instance details

Defined in NixTree.StorePath

type Rep StoreName Source # 
Instance details

Defined in NixTree.StorePath

data NixPathSignature Source #

Constructors

NixPathSignature 

Instances

Instances details
FromJSON NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

Generic NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

Associated Types

type Rep NixPathSignature 
Instance details

Defined in NixTree.StorePath

type Rep NixPathSignature = D1 ('MetaData "NixPathSignature" "NixTree.StorePath" "nix-tree-0.7.0-HNPzNedb4REJMzrrj53EmD" 'False) (C1 ('MetaCons "NixPathSignature" 'PrefixI 'True) (S1 ('MetaSel ('Just "npsKeyName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "npsSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
Show NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

NFData NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

Methods

rnf :: NixPathSignature -> () #

Eq NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

Ord NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

type Rep NixPathSignature Source # 
Instance details

Defined in NixTree.StorePath

type Rep NixPathSignature = D1 ('MetaData "NixPathSignature" "NixTree.StorePath" "nix-tree-0.7.0-HNPzNedb4REJMzrrj53EmD" 'False) (C1 ('MetaCons "NixPathSignature" 'PrefixI 'True) (S1 ('MetaSel ('Just "npsKeyName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "npsSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data StorePath ref payload Source #

Constructors

StorePath 

Fields

Instances

Instances details
Functor (StorePath ref) Source # 
Instance details

Defined in NixTree.StorePath

Methods

fmap :: (a -> b) -> StorePath ref a -> StorePath ref b #

(<$) :: a -> StorePath ref b -> StorePath ref a #

Generic (StorePath ref payload) Source # 
Instance details

Defined in NixTree.StorePath

Associated Types

type Rep (StorePath ref payload) 
Instance details

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])))))

Methods

from :: StorePath ref payload -> Rep (StorePath ref payload) x #

to :: Rep (StorePath ref payload) x -> StorePath ref payload #

(Show ref, Show payload) => Show (StorePath ref payload) Source # 
Instance details

Defined in NixTree.StorePath

Methods

showsPrec :: Int -> StorePath ref payload -> ShowS #

show :: StorePath ref payload -> String #

showList :: [StorePath ref payload] -> ShowS #

(NFData a, NFData b) => NFData (StorePath a b) Source # 
Instance details

Defined in NixTree.StorePath

Methods

rnf :: StorePath a b -> () #

(Eq ref, Eq payload) => Eq (StorePath ref payload) Source # 
Instance details

Defined in NixTree.StorePath

Methods

(==) :: StorePath ref payload -> StorePath ref payload -> Bool #

(/=) :: StorePath ref payload -> StorePath ref payload -> Bool #

(Ord ref, Ord payload) => Ord (StorePath ref payload) Source # 
Instance details

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 # 
Instance details

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 

data StoreEnv payload Source #

Instances

Instances details
Functor StoreEnv Source # 
Instance details

Defined in NixTree.StorePath

Methods

fmap :: (a -> b) -> StoreEnv a -> StoreEnv b #

(<$) :: a -> StoreEnv b -> StoreEnv a #

Generic (StoreEnv payload) Source # 
Instance details

Defined in NixTree.StorePath

Associated Types

type Rep (StoreEnv payload) 
Instance details

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))))

Methods

from :: StoreEnv payload -> Rep (StoreEnv payload) x #

to :: Rep (StoreEnv payload) x -> StoreEnv payload #

NFData payload => NFData (StoreEnv payload) Source # 
Instance details

Defined in NixTree.StorePath

Methods

rnf :: StoreEnv payload -> () #

type Rep (StoreEnv payload) Source # 
Instance details

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))))

seBottomUp :: forall a b. (StorePath (StorePath StoreName b) a -> b) -> StoreEnv a -> StoreEnv b Source #