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

System.Nix.Derivation

Synopsis

Documentation

data Derivation fp txt #

A Nix derivation

Constructors

Derivation 

Fields

  • outputs :: Map txt (DerivationOutput fp txt)

    Outputs produced by this derivation where keys are output names

  • inputDrvs :: Map fp (Set txt)

    Inputs that are derivations where keys specify derivation paths and values specify which output names are used by this derivation

  • inputSrcs :: Set fp

    Inputs that are sources

  • platform :: txt

    Platform required for this derivation

  • builder :: txt

    Code to build the derivation, which can be a path or a builtin function

  • args :: Vector txt

    Arguments passed to the executable used to build to derivation

  • env :: Map txt txt

    Environment variables provided to the executable used to build the derivation

Instances

Instances details
Generic (Derivation fp txt) 
Instance details

Defined in Nix.Derivation.Types

Associated Types

type Rep (Derivation fp txt) :: Type -> Type #

Methods

from :: Derivation fp txt -> Rep (Derivation fp txt) x #

to :: Rep (Derivation fp txt) x -> Derivation fp txt #

(Show fp, Show txt) => Show (Derivation fp txt) 
Instance details

Defined in Nix.Derivation.Types

Methods

showsPrec :: Int -> Derivation fp txt -> ShowS #

show :: Derivation fp txt -> String #

showList :: [Derivation fp txt] -> ShowS #

(NFData a, NFData b) => NFData (Derivation a b) 
Instance details

Defined in Nix.Derivation.Types

Methods

rnf :: Derivation a b -> () #

(Eq fp, Eq txt) => Eq (Derivation fp txt) 
Instance details

Defined in Nix.Derivation.Types

Methods

(==) :: Derivation fp txt -> Derivation fp txt -> Bool #

(/=) :: Derivation fp txt -> Derivation fp txt -> Bool #

(Ord fp, Ord txt) => Ord (Derivation fp txt) 
Instance details

Defined in Nix.Derivation.Types

Methods

compare :: Derivation fp txt -> Derivation fp txt -> Ordering #

(<) :: Derivation fp txt -> Derivation fp txt -> Bool #

(<=) :: Derivation fp txt -> Derivation fp txt -> Bool #

(>) :: Derivation fp txt -> Derivation fp txt -> Bool #

(>=) :: Derivation fp txt -> Derivation fp txt -> Bool #

max :: Derivation fp txt -> Derivation fp txt -> Derivation fp txt #

min :: Derivation fp txt -> Derivation fp txt -> Derivation fp txt #

type Rep (Derivation fp txt) 
Instance details

Defined in Nix.Derivation.Types

type Rep (Derivation fp txt) = D1 ('MetaData "Derivation" "Nix.Derivation.Types" "nix-derivation-1.1.3-8HLZlIqMkg5EsTkYPnN9je" 'False) (C1 ('MetaCons "Derivation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "outputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map txt (DerivationOutput fp txt))) :*: (S1 ('MetaSel ('Just "inputDrvs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map fp (Set txt))) :*: S1 ('MetaSel ('Just "inputSrcs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set fp)))) :*: ((S1 ('MetaSel ('Just "platform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 txt) :*: S1 ('MetaSel ('Just "builder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 txt)) :*: (S1 ('MetaSel ('Just "args") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector txt)) :*: S1 ('MetaSel ('Just "env") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map txt txt))))))

data DerivationOutput fp txt #

An output of a Nix derivation

Constructors

DerivationOutput 

Fields

  • path :: fp

    Path where the output will be saved

  • hashAlgo :: txt

    Hash used for expected hash computation

  • hash :: txt

    Expected hash

Instances

Instances details
Bifunctor DerivationOutput 
Instance details

Defined in Nix.Derivation.Types

Methods

bimap :: (a -> b) -> (c -> d) -> DerivationOutput a c -> DerivationOutput b d #

first :: (a -> b) -> DerivationOutput a c -> DerivationOutput b c #

second :: (b -> c) -> DerivationOutput a b -> DerivationOutput a c #

Functor (DerivationOutput fp) 
Instance details

Defined in Nix.Derivation.Types

Methods

fmap :: (a -> b) -> DerivationOutput fp a -> DerivationOutput fp b #

(<$) :: a -> DerivationOutput fp b -> DerivationOutput fp a #

Generic (DerivationOutput fp txt) 
Instance details

Defined in Nix.Derivation.Types

Associated Types

type Rep (DerivationOutput fp txt) :: Type -> Type #

Methods

from :: DerivationOutput fp txt -> Rep (DerivationOutput fp txt) x #

to :: Rep (DerivationOutput fp txt) x -> DerivationOutput fp txt #

(Show fp, Show txt) => Show (DerivationOutput fp txt) 
Instance details

Defined in Nix.Derivation.Types

Methods

showsPrec :: Int -> DerivationOutput fp txt -> ShowS #

show :: DerivationOutput fp txt -> String #

showList :: [DerivationOutput fp txt] -> ShowS #

(NFData a, NFData b) => NFData (DerivationOutput a b) 
Instance details

Defined in Nix.Derivation.Types

Methods

rnf :: DerivationOutput a b -> () #

(Eq fp, Eq txt) => Eq (DerivationOutput fp txt) 
Instance details

Defined in Nix.Derivation.Types

Methods

(==) :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool #

(/=) :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool #

(Ord fp, Ord txt) => Ord (DerivationOutput fp txt) 
Instance details

Defined in Nix.Derivation.Types

Methods

compare :: DerivationOutput fp txt -> DerivationOutput fp txt -> Ordering #

(<) :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool #

(<=) :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool #

(>) :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool #

(>=) :: DerivationOutput fp txt -> DerivationOutput fp txt -> Bool #

max :: DerivationOutput fp txt -> DerivationOutput fp txt -> DerivationOutput fp txt #

min :: DerivationOutput fp txt -> DerivationOutput fp txt -> DerivationOutput fp txt #

type Rep (DerivationOutput fp txt) 
Instance details

Defined in Nix.Derivation.Types

type Rep (DerivationOutput fp txt) = D1 ('MetaData "DerivationOutput" "Nix.Derivation.Types" "nix-derivation-1.1.3-8HLZlIqMkg5EsTkYPnN9je" 'False) (C1 ('MetaCons "DerivationOutput" 'PrefixI 'True) (S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 fp) :*: (S1 ('MetaSel ('Just "hashAlgo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 txt) :*: S1 ('MetaSel ('Just "hash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 txt))))