nix-derivation-1.1.2: Parse and render *.drv files
Safe HaskellNone
LanguageHaskell2010

Nix.Derivation

Description

Use this package to parse and render Nix derivations such as those stored in /nix/store/*.drv files. For example, if you had the following derivation saved at /nix/store/zzhs4fb83x5ygvjqn5rdpmpnishpdgy6-perl-MIME-Types-2.13.drv:

Derive([("devdoc","/nix/store/15x9ii8c3n5wb5lg80cm8x0yk6zy7rha-perl-MIME-Types-2
.13-devdoc","",""),("out","/nix/store/93d75ghjyibmbxgfzwhh4b5zwsxzs44w-perl-MIME
-Types-2.13","","")],[("/nix/store/57h2hjsdkdiwbzilcjqkn46138n1xb4a-perl-5.22.3.
drv",["out"]),("/nix/store/cvdbbvnvg131bz9bwyyk97jpq1crclqr-MIME-Types-2.13.tar.
gz.drv",["out"]),("/nix/store/p5g31bc5x92awghx9dlm065d7j773l0r-stdenv.drv",["out
"]),("/nix/store/x50y5qihwsn0lfjhrf1s81b5hgb9w632-bash-4.4-p5.drv",["out"])],["/
nix/store/cdips4lakfk1qbf1x68fq18wnn3r5r14-builder.sh"],"x86_64-linux","/nix/sto
re/fi3mbd2ml4pbgzyasrlnp0wyy6qi48fh-bash-4.4-p5/bin/bash",["-e","/nix/store/cdip
s4lakfk1qbf1x68fq18wnn3r5r14-builder.sh"],[("AUTOMATED_TESTING","1"),("PERL_AUTO
INSTALL","--skipdeps"),("buildInputs",""),("builder","/nix/store/fi3mbd2ml4pbgzy
asrlnp0wyy6qi48fh-bash-4.4-p5/bin/bash"),("checkTarget","test"),("devdoc","/nix/
store/15x9ii8c3n5wb5lg80cm8x0yk6zy7rha-perl-MIME-Types-2.13-devdoc"),("doCheck",
"1"),("installTargets","pure_install"),("name","perl-MIME-Types-2.13"),("nativeB
uildInputs","/nix/store/nsa311yg8h93wfaacjk16c96a98bs09f-perl-5.22.3"),("out","/
nix/store/93d75ghjyibmbxgfzwhh4b5zwsxzs44w-perl-MIME-Types-2.13"),("outputs","ou
t devdoc"),("propagatedBuildInputs",""),("propagatedNativeBuildInputs",""),("src
","/nix/store/5smhymz7viq8p47mc3jgyvqd003ab732-MIME-Types-2.13.tar.gz"),("stdenv
","/nix/store/s3rlr45jzlzx0d6k2azlpxa5zwzr7xyy-stdenv"),("system","x86_64-linux"
)])

... you could parse that derivation using:

>>> text <- Data.Text.Lazy.IO.readFile "/nix/store/zzhs4fb83x5ygvjqn5rdpmpnishpdgy6-perl-MIME-Types-2.13.drv"
>>> let result = Data.Attoparsec.Text.Lazy.parse Nix.Derivation.parseDerivation text
>>> result
Done "" (Derivation {outputs = fromList [("devdoc",DerivationOutput {path = File
Path "/nix/store/15x9ii8c3n5wb5lg80cm8x0yk6zy7rha-perl-MIME-Types-2.13-devdoc", 
hashAlgo = "", hash = ""}),("out",DerivationOutput {path = FilePath "/nix/store/
93d75ghjyibmbxgfzwhh4b5zwsxzs44w-perl-MIME-Types-2.13", hashAlgo = "", hash = ""
})], inputDrvs = fromList [(FilePath "/nix/store/57h2hjsdkdiwbzilcjqkn46138n1xb4
a-perl-5.22.3.drv",fromList ["out"]),(FilePath "/nix/store/cvdbbvnvg131bz9bwyyk9
7jpq1crclqr-MIME-Types-2.13.tar.gz.drv",fromList ["out"]),(FilePath "/nix/store/
p5g31bc5x92awghx9dlm065d7j773l0r-stdenv.drv",fromList ["out"]),(FilePath "/nix/s
tore/x50y5qihwsn0lfjhrf1s81b5hgb9w632-bash-4.4-p5.drv",fromList ["out"])], input
Srcs = fromList [FilePath "/nix/store/cdips4lakfk1qbf1x68fq18wnn3r5r14-builder.s
h"], platform = "x86_64-linux", builder = FilePath "/nix/store/fi3mbd2ml4pbgzyas
rlnp0wyy6qi48fh-bash-4.4-p5/bin/bash", args = ["-e","/nix/store/cdips4lakfk1qbf1
x68fq18wnn3r5r14-builder.sh"], env = fromList [("AUTOMATED_TESTING","1"),("PERL_
AUTOINSTALL","--skipdeps"),("buildInputs",""),("builder","/nix/store/fi3mbd2ml4p
bgzyasrlnp0wyy6qi48fh-bash-4.4-p5/bin/bash"),("checkTarget","test"),("devdoc","/
nix/store/15x9ii8c3n5wb5lg80cm8x0yk6zy7rha-perl-MIME-Types-2.13-devdoc"),("doChe
ck","1"),("installTargets","pure_install"),("name","perl-MIME-Types-2.13"),("nat
iveBuildInputs","/nix/store/nsa311yg8h93wfaacjk16c96a98bs09f-perl-5.22.3"),("out
","/nix/store/93d75ghjyibmbxgfzwhh4b5zwsxzs44w-perl-MIME-Types-2.13"),("outputs"
,"out devdoc"),("propagatedBuildInputs",""),("propagatedNativeBuildInputs",""),(
"src","/nix/store/5smhymz7viq8p47mc3jgyvqd003ab732-MIME-Types-2.13.tar.gz"),("st
denv","/nix/store/s3rlr45jzlzx0d6k2azlpxa5zwzr7xyy-stdenv"),("system","x86_64-li
nux")]})

... and render the result back to the original derivation:

>>> fmap buildDerivation result
Done "" "Derive([(\"devdoc\",\"/nix/store/15x9ii8c3n5wb5lg80cm8x0yk6zy7rha-perl-
MIME-Types-2.13-devdoc\",\"\",\"\"),(\"out\",\"/nix/store/93d75ghjyibmbxgfzwhh4b
5zwsxzs44w-perl-MIME-Types-2.13\",\"\",\"\")],[(\"/nix/store/57h2hjsdkdiwbzilcjq
kn46138n1xb4a-perl-5.22.3.drv\",[\"out\"]),(\"/nix/store/cvdbbvnvg131bz9bwyyk97j
pq1crclqr-MIME-Types-2.13.tar.gz.drv\",[\"out\"]),(\"/nix/store/p5g31bc5x92awghx
9dlm065d7j773l0r-stdenv.drv\",[\"out\"]),(\"/nix/store/x50y5qihwsn0lfjhrf1s81b5h
gb9w632-bash-4.4-p5.drv\",[\"out\"])],[\"/nix/store/cdips4lakfk1qbf1x68fq18wnn3r
5r14-builder.sh\"],\"x86_64-linux\",\"/nix/store/fi3mbd2ml4pbgzyasrlnp0wyy6qi48f
h-bash-4.4-p5/bin/bash\",[\"-e\",\"/nix/store/cdips4lakfk1qbf1x68fq18wnn3r5r14-b
uilder.sh\"],[(\"AUTOMATED_TESTING\",\"1\"),(\"PERL_AUTOINSTALL\",\"--skipdeps\"
),(\"buildInputs\",\"\"),(\"builder\",\"/nix/store/fi3mbd2ml4pbgzyasrlnp0wyy6qi4
8fh-bash-4.4-p5/bin/bash\"),(\"checkTarget\",\"test\"),(\"devdoc\",\"/nix/store/
15x9ii8c3n5wb5lg80cm8x0yk6zy7rha-perl-MIME-Types-2.13-devdoc\"),(\"doCheck\",\"1
\"),(\"installTargets\",\"pure_install\"),(\"name\",\"perl-MIME-Types-2.13\"),(\
"nativeBuildInputs\",\"/nix/store/nsa311yg8h93wfaacjk16c96a98bs09f-perl-5.22.3\"
),(\"out\",\"/nix/store/93d75ghjyibmbxgfzwhh4b5zwsxzs44w-perl-MIME-Types-2.13\")
,(\"outputs\",\"out devdoc\"),(\"propagatedBuildInputs\",\"\"),(\"propagatedNati
veBuildInputs\",\"\"),(\"src\",\"/nix/store/5smhymz7viq8p47mc3jgyvqd003ab732-MIM
E-Types-2.13.tar.gz\"),(\"stdenv\",\"/nix/store/s3rlr45jzlzx0d6k2azlpxa5zwzr7xyy
-stdenv\"),(\"system\",\"x86_64-linux\")])"
Synopsis

Types

data Derivation fp txt Source #

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
(Eq txt, Eq fp) => Eq (Derivation fp txt) Source # 
Instance details

Defined in Nix.Derivation.Types

Methods

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

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

(Ord txt, Ord fp) => Ord (Derivation fp txt) Source # 
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 #

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

Defined in Nix.Derivation.Types

Methods

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

show :: Derivation fp txt -> String #

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

Generic (Derivation fp txt) Source # 
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 #

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

Defined in Nix.Derivation.Types

Methods

rnf :: Derivation a b -> () #

type Rep (Derivation fp txt) Source # 
Instance details

Defined in Nix.Derivation.Types

type Rep (Derivation fp txt) = D1 ('MetaData "Derivation" "Nix.Derivation.Types" "nix-derivation-1.1.2-GH2X0x0mQQhA7iLcH2PD5M" '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 Source #

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
(Eq fp, Eq txt) => Eq (DerivationOutput fp txt) Source # 
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) Source # 
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 #

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

Defined in Nix.Derivation.Types

Methods

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

show :: DerivationOutput fp txt -> String #

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

Generic (DerivationOutput fp txt) Source # 
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 #

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

Defined in Nix.Derivation.Types

Methods

rnf :: DerivationOutput a b -> () #

type Rep (DerivationOutput fp txt) Source # 
Instance details

Defined in Nix.Derivation.Types

type Rep (DerivationOutput fp txt) = D1 ('MetaData "DerivationOutput" "Nix.Derivation.Types" "nix-derivation-1.1.2-GH2X0x0mQQhA7iLcH2PD5M" '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))))

Parse derivations

parseDerivationWith :: (Ord fp, Ord txt) => Parser fp -> Parser txt -> Parser (Derivation fp txt) Source #

Parse a derivation using custom parsers for filepaths and text fields

Render derivations

buildDerivationWith :: (fp -> Builder) -> (txt -> Builder) -> Derivation fp txt -> Builder Source #

Render a derivation as a Builder using custom renderer for filepath and string