cabal2nix-2.18.0: 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

Instances details
Eq Source Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Methods

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

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

Ord Source Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Show Source Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Generic Source Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Associated Types

type Rep Source :: Type -> Type #

Methods

from :: Source -> Rep Source x #

to :: Rep Source x -> Source #

NFData Source Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Methods

rnf :: Source -> () #

type Rep Source Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

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

data Hash Source #

Instances

Instances details
Eq Hash Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Methods

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

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

Ord Hash Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

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

Defined in Distribution.Nixpkgs.Fetch

Methods

showsPrec :: Int -> Hash -> ShowS #

show :: Hash -> String #

showList :: [Hash] -> ShowS #

Generic Hash Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Associated Types

type Rep Hash :: Type -> Type #

Methods

from :: Hash -> Rep Hash x #

to :: Rep Hash x -> Hash #

NFData Hash Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Methods

rnf :: Hash -> () #

type Rep Hash Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

type Rep Hash = D1 ('MetaData "Hash" "Distribution.Nixpkgs.Fetch" "cabal2nix-2.18.0-AxzODvrDwmLCfl7usD518l" 'False) (C1 ('MetaCons "Certain" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "Guess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "UnknownHash" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
Eq DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Ord DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Show DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Generic DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Associated Types

type Rep DerivationSource :: Type -> Type #

NFData DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Methods

rnf :: DerivationSource -> () #

FromJSON DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

Pretty DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

type Rep DerivationSource Source # 
Instance details

Defined in Distribution.Nixpkgs.Fetch

type Rep DerivationSource = D1 ('MetaData "DerivationSource" "Distribution.Nixpkgs.Fetch" "cabal2nix-2.18.0-AxzODvrDwmLCfl7usD518l" 'False) (C1 ('MetaCons "DerivationSource" 'PrefixI 'True) ((S1 ('MetaSel ('Just "derivKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "derivUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "derivRevision") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "derivHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "derivSubmodule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

fetch Source #

Arguments

:: forall a. Bool

If True, fetch submodules when the source is a git repository

-> (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, Maybe String, [String]) -> Source -> MaybeT IO (DerivationSource, FilePath) Source #

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