cabal2nix-2.7.2: Convert Cabal files into Nix build instructions.

Safe HaskellNone
LanguageHaskell2010

Distribution.Nixpkgs.Fetch

Synopsis

Documentation

data Source Source #

A source is a location from which we can fetch, such as a HTTP URL, a GIT URL, ....

Constructors

Source 

Fields

Instances

Eq Source Source # 

Methods

(==) :: Source -> Source -> Bool #

(/=) :: Source -> Source -> Bool #

Ord Source Source # 
Show Source Source # 
Generic Source Source # 

Associated Types

type Rep Source :: * -> * #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

NFData Source Source # 

Methods

rnf :: Source -> () #

type Rep Source Source # 
type Rep Source = D1 * (MetaData "Source" "Distribution.Nixpkgs.Fetch" "cabal2nix-2.7.2-Ejf4Mkdmv6ALyXtK9ug5gO" False) (C1 * (MetaCons "Source" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "sourceUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "sourceRevision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "sourceHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Hash)) (S1 * (MetaSel (Just Symbol "sourceCabalDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))

data Hash Source #

Instances

Eq Hash Source # 

Methods

(==) :: Hash -> Hash -> Bool #

(/=) :: Hash -> Hash -> Bool #

Ord Hash Source # 

Methods

compare :: Hash -> Hash -> Ordering #

(<) :: Hash -> Hash -> Bool #

(<=) :: Hash -> Hash -> Bool #

(>) :: Hash -> Hash -> Bool #

(>=) :: Hash -> Hash -> Bool #

max :: Hash -> Hash -> Hash #

min :: Hash -> Hash -> Hash #

Show Hash Source # 

Methods

showsPrec :: Int -> Hash -> ShowS #

show :: Hash -> String #

showList :: [Hash] -> ShowS #

Generic Hash Source # 

Associated Types

type Rep Hash :: * -> * #

Methods

from :: Hash -> Rep Hash x #

to :: Rep Hash x -> Hash #

NFData Hash Source # 

Methods

rnf :: Hash -> () #

type Rep Hash Source # 
type Rep Hash = D1 * (MetaData "Hash" "Distribution.Nixpkgs.Fetch" "cabal2nix-2.7.2-Ejf4Mkdmv6ALyXtK9ug5gO" False) ((:+:) * (C1 * (MetaCons "Certain" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:+:) * (C1 * (MetaCons "Guess" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "UnknownHash" PrefixI False) (U1 *))))

data DerivationSource Source #

A source for a derivation. It always needs a hash and also has a protocol attached to it (url, git, svn, ...). A DerivationSource also always has it's revision fully resolved (not relative revisions like master, HEAD, etc).

Constructors

DerivationSource 

Fields

Instances

Eq DerivationSource Source # 
Ord DerivationSource Source # 
Show DerivationSource Source # 
Generic DerivationSource Source # 
NFData DerivationSource Source # 

Methods

rnf :: DerivationSource -> () #

FromJSON DerivationSource Source # 
type Rep DerivationSource Source # 
type Rep DerivationSource = D1 * (MetaData "DerivationSource" "Distribution.Nixpkgs.Fetch" "cabal2nix-2.7.2-Ejf4Mkdmv6ALyXtK9ug5gO" False) (C1 * (MetaCons "DerivationSource" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "derivKind") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "derivUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "derivRevision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "derivHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))

fetch Source #

Arguments

:: (String -> MaybeT IO a)

This function is passed the output path name as an argument. It should return Nothing if the file doesn't match the expected format. This is required, because we cannot always check if a download succeeded otherwise.

-> Source

The source to fetch from.

-> IO (Maybe (DerivationSource, a))

The derivation source and the result of the processing function. Returns Nothing if the download failed.

Fetch a source, trying any of the various nix-prefetch-* scripts.

fetchWith :: (Bool, String, [String]) -> Source -> MaybeT IO (DerivationSource, FilePath) Source #

Like fetch, but allows to specify which script to use.