nvfetcher-0.6.1.0: Generate nix sources expr for the latest version of packages
Copyright(c) 2021-2022 berberman
LicenseMIT
Maintainerberberman <berberman@yandex.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

NvFetcher.PackageSet

Description

This module mainly contains two things: PackageSet and PkgDSL. NvFetcher accepts the former one -- a set of packages to produce nix sources expr; the later one is used to construct a single package.

There are many combinators for defining packages. See the documentation of define for example.

Synopsis

Package set

data PackageSetF f Source #

Atomic terms of package set

Instances

Instances details
MonadIO PackageSet Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

liftIO :: IO a -> PackageSet a #

Functor PackageSetF Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

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

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

PkgDSL PackageSet Source # 
Instance details

Defined in NvFetcher.PackageSet

type PackageSet = Free PackageSetF Source #

Package set is a monad equipped with two capabilities:

  1. Carry defined packages
  2. Run IO actions

Package set is evaluated before shake runs. Use newPackage to add a new package, liftIO to run an IO action.

purePackageSet :: [Package] -> PackageSet () Source #

Add a list of packages into package set

runPackageSet :: PackageSet () -> IO (Map PackageKey Package) Source #

Run package set into a set of packages

Throws exception as more then one packages with the same name are defined

Package DSL

Primitives

package :: PackageName -> PackageSet (Prod '[PackageName]) Source #

Start chaining with the name of package to define

src :: Attach VersionSource VersionSource Source #

Attach version sources

Two-in-one functions

Version sources

sourceGitHub :: Attach VersionSource (Text, Text) Source #

This package follows the latest github release

sourceGitHubTag :: Attach VersionSource (Text, Text, ListOptions -> ListOptions) Source #

This package follows the a tag from github

Args are owner, repo, and nvchecker list options to find the target tag

sourceGit :: Attach VersionSource Text Source #

This package follows the latest git commit

Arg is git url

sourceGit' :: Attach VersionSource (Text, Text) Source #

Similar to sourceGit, but allows to specify branch

Args are git url and branch

sourcePypi :: Attach VersionSource Text Source #

This package follows the latest pypi release

Arg is pypi name

sourceAur :: Attach VersionSource Text Source #

This package follows the version of an Aur package

Arg is package name in Aur

sourceArchLinux :: Attach VersionSource Text Source #

This package follows the version of an Arch Linux package

Arg is package name in Arch Linux repo

sourceManual :: Attach VersionSource Text Source #

This package follows a pinned version

Arg is manual version

sourceRepology :: Attach VersionSource (Text, Text) Source #

This package follows the version of a repology package

Args are repology project name and repo

sourceWebpage :: Attach VersionSource (Text, Text, ListOptions -> ListOptions) Source #

This package follows a version extracted from web page

Args are web page url, regex, and list options

sourceHttpHeader :: Attach VersionSource (Text, Text, ListOptions -> ListOptions) Source #

This package follows a version extracted from http header

Args are the url of the http request, regex, and list options

sourceOpenVsx :: Attach VersionSource (Text, Text) Source #

This package follows a version in Open VSX

Args are publisher and extension name

sourceVscodeMarketplace :: Attach VersionSource (Text, Text) Source #

This package follows a version in Vscode Marketplace

Args are publisher and extension name

sourceCmd :: Attach VersionSource Text Source #

This package follows a version from a shell command

Arg is the command to run

Fetchers

fetchGitHub :: Attach PackageFetcher (Text, Text) Source #

This package is fetched from a github repo

Args are owner and repo

fetchGitHub' :: Attach PackageFetcher (Text, Text, NixFetcher Fresh -> NixFetcher Fresh) Source #

This package is fetched from a github repo

Similar to fetchGitHub, but allows a modifier to the fetcher. For example, you can enable fetch submodules like:

define $ package "qliveplayer" sourceGitHub (THMonster, QLivePlayer) fetchGitHub` (THMonster, QLivePlayer, fetchSubmodules .~ True)

fetchGitHubRelease :: Attach PackageFetcher (Text, Text, Text) Source #

This package is fetched from a file in github release

Args are owner, repo, and file name

fetchGitHubRelease' :: Attach PackageFetcher (Text, Text, Version -> Text) Source #

This package is fetched from a file in github release

Args are owner, repo, and file name computed from version

fetchPypi :: Attach PackageFetcher Text Source #

This package is fetched from pypi

Arg is pypi name

fetchGit :: Attach PackageFetcher Text Source #

This package is fetched from git

Arg is git url

fetchGit' :: Attach PackageFetcher (Text, NixFetcher Fresh -> NixFetcher Fresh) Source #

This package is fetched from git

Similar to fetchGit, but allows a modifier to the fetcher. See fetchGitHub' for a concret example.

fetchUrl :: Attach PackageFetcher (Version -> Text) Source #

This package is fetched from url

Arg is a function which constructs the url from a version

fetchOpenVsx :: Attach PackageFetcher (Text, Text) Source #

This package is fetched from Open VSX

Args are publisher and extension name

fetchVscodeMarketplace :: Attach PackageFetcher (Text, Text) Source #

This package is fetched from Vscode Marketplace

Args are publisher and extension name

fetchTarball :: Attach PackageFetcher (Version -> Text) Source #

This package is a tarball, fetched from url

Arg is a function which constructs the url from a version

Addons

extractSource :: Attach PackageExtractSrc [FilePath] Source #

Extract files from fetched package source

hasCargoLocks :: Attach PackageCargoLockFiles [FilePath] Source #

Run FetchRustGitDependencies given the path to Cargo.lock files

The lock files will be extracted as well.

tweakVersion :: Attach NvcheckerOptions (NvcheckerOptions -> NvcheckerOptions) Source #

Set NvcheckerOptions for a package, which can tweak the version number we obtain

passthru :: Attach PackagePassthru [(Text, Text)] Source #

An attrs set to pass through

Arg is a list of kv pairs

pinned :: PackageSet (Prod r) -> PackageSet (Prod (UseStaleVersion ': r)) Source #

Pin a package

new version won't be checked if we have a stale version

gitDateFormat :: Attach DateFormat (Maybe Text) Source #

Specify the date format for getting git commit date

Available only for git version source

forceFetch :: PackageSet (Prod r) -> PackageSet (Prod (ForceFetch ': r)) Source #

Set always fetching regardless of the version changing

Miscellaneous

data Prod (r :: [Type]) Source #

Simple HList

type family Append xs ys where ... Source #

xs ++ ys, at type level

Equations

Append '[] ys = ys 
Append (x ': xs) ys = x ': Append xs ys 

class Member (a :: Type) (r :: [Type]) Source #

Project elements from Prod

Minimal complete definition

proj

Instances

Instances details
(TypeError ('ShowType x :<>: 'Text " is undefined") :: Constraint) => Member x ('[] :: [Type]) Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

proj :: Prod '[] -> x

Member x xs => Member x (_y ': xs) Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

proj :: Prod (_y ': xs) -> x

NotElem x xs => Member x (x ': xs) Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

proj :: Prod (x ': xs) -> x

class OptionalMember (a :: Type) (r :: [Type]) Source #

Project optional elements from Prod

Minimal complete definition

projMaybe

Instances

Instances details
OptionalMember x ('[] :: [Type]) Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

projMaybe :: Prod '[] -> Maybe x

OptionalMember x xs => OptionalMember x (_y ': xs) Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

projMaybe :: Prod (_y ': xs) -> Maybe x

NotElem x xs => OptionalMember x (x ': xs) Source # 
Instance details

Defined in NvFetcher.PackageSet

Methods

projMaybe :: Prod (x ': xs) -> Maybe x

type family NotElem (x :: Type) (xs :: [Type]) :: Constraint where ... Source #

Constraint for producing error messages

Equations

NotElem x (x ': xs) = TypeError (ShowType x :<>: 'Text " is defined more than one times") 
NotElem x (_ ': xs) = NotElem x xs 
NotElem x '[] = () 

type family Members xs r :: Constraint where ... Source #

A list of Member

Equations

Members '[] _ = () 
Members (x ': xs) r = (Member x r, Members xs r) 

type family OptionalMembers xs r :: Constraint where ... Source #

A list of OptionalMember

Equations

OptionalMembers '[] _ = () 
OptionalMembers (x ': xs) r = (OptionalMember x r, OptionalMembers xs r) 

type Attach x arg = AttachMany '[x] arg Source #

Attach member x, with a function arg

type AttachMany xs arg = forall r. PackageSet (Prod r) -> arg -> PackageSet (Prod (Append xs r)) Source #

Attach members xs, with a function argument arg

coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b #

The function coerce allows you to safely convert between values of types that have the same representation with no run-time overhead. In the simplest case you can use it instead of a newtype constructor, to go from the newtype's concrete type to the abstract type. But it also works in more complicated settings, e.g. converting a list of newtypes to a list of concrete types.

This function is runtime-representation polymorphic, but the RuntimeRep type argument is marked as Inferred, meaning that it is not available for visible type application. This means the typechecker will accept coerce @Int @Age 42.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

Lenses

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #

(.~) assigns a value to the target. It's the same thing as using (%~) with const:

l .~ x = l %~ const x

See set if you want a non-operator synonym.

Here it is used to change 2 fields of a 3-tuple:

>>> (0,0,0) & _1 .~ 1 & _3 .~ 3
(1,0,3)

(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #

(%~) applies a function to the target; an alternative explanation is that it is an inverse of sets, which turns a setter into an ordinary function. mapped %~ reverse is the same thing as fmap reverse.

See over if you want a non-operator synonym.

Negating the 1st element of a pair:

>>> (1,2) & _1 %~ negate
(-1,2)

Turning all Lefts in a list to upper case:

>>> (mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]

(^.) :: s -> Getting a s a -> a infixl 8 #

(^.) applies a getter to a value; in other words, it gets a value out of a structure using a getter (which can be a lens, traversal, fold, etc.).

Getting 1st field of a tuple:

(^. _1) :: (a, b) -> a
(^. _1) = fst

When (^.) is used with a traversal, it combines all results using the Monoid instance for the resulting type. For instance, for lists it would be simple concatenation:

>>> ("str","ing") ^. each
"string"

The reason for this is that traversals use Applicative, and the Applicative instance for Const uses monoid concatenation to combine “effects” of Const.

A non-operator version of (^.) is called view, and it's a bit more general than (^.) (it works in MonadReader). If you need the general version, you can get it from microlens-mtl; otherwise there's view available in Lens.Micro.Extras.

(?~) :: ASetter s t a (Maybe b) -> b -> s -> t infixr 4 #

(?~) is a version of (.~) that wraps the value into Just before setting.

l ?~ b = l .~ Just b

It can be useful in combination with at:

>>> Map.empty & at 3 ?~ x
fromList [(3,x)]