nixfromnpm-0.1.0.6: Generate nix expressions from npm packages.

Safe HaskellNone
LanguageHaskell2010

NixFromNpm

Synopsis

Documentation

module Data.Char

module Data.Maybe

module Data.List

module GHC.Exts

type Name = Text Source

Indicates that the text is some identifier.

type Record = HashMap Name Source

A record is a lookup table with string keys.

tuple :: Applicative f => f a -> f b -> f (a, b) Source

Takes two applicative actions and returns their result as a 2-tuple.

tuple3 :: Applicative f => f a -> f b -> f c -> f (a, b, c) Source

Takes three applicative actions and returns their result as a 3-tuple.

fromRight :: Either a b -> b Source

cerror :: [String] -> a Source

cerror' :: [Text] -> a Source

slash :: URI -> Text -> URI infixl 6 Source

Appends text to URI with a slash. Ex: foo.com slash bar == foo.com/bar.

putStrsLn :: MonadIO m => [Text] -> m () Source

putStrs :: MonadIO m => [Text] -> m () Source

maybeIf :: Bool -> a -> Maybe a Source

grab :: (Hashable k, Eq k) => k -> HashMap k v -> v Source

withDir :: String -> IO a -> IO a Source

mapJoinBy :: Text -> (a -> Text) -> [a] -> Text Source

type SemVer = (Int, Int, Int) Source

data Wildcard Source

A partially specified semantic version. Implicitly defines a range of acceptable versions, as seen in wildcardToRange.

Constructors

Any 
One Int 
Two Int Int 
Three Int Int Int 

matches :: SemVerRange -> SemVer -> Bool Source

Returns whether a given semantic version matches a range.

bestMatch :: SemVerRange -> [SemVer] -> Either String SemVer Source

Gets the highest-matching semver in a range.

wildcardToSemver :: Wildcard -> SemVer Source

Fills in zeros in a wildcard.

wildcardToRange :: Wildcard -> SemVerRange Source

Translates a wildcard (partially specified version) to a range. Ex: 2 := >=2.0.0 <3.0.0 Ex: 1.2.x := 1.2 := >=1.2.0 <1.3.0

tildeToRange :: Wildcard -> SemVerRange Source

Translates a ~wildcard to a range. Ex: ~1.2.3 := >=1.2.3 :==1.2.3 <1.3.0

caratToRange :: Wildcard -> SemVerRange Source

Translates a ^wildcard to a range. Ex: ^1.2.x := >=1.2.0 <2.0.0

hyphenatedRange :: Wildcard -> Wildcard -> SemVerRange Source

Translates two hyphenated wildcards to an actual range. Ex: 1.2.3 - 2.3.4 := >=1.2.3 <=2.3.4 Ex: 1.2 - 2.3.4 := >=1.2.0 <=2.3.4 Ex: 1.2.3 - 2 := >=1.2.3 <3.0.0

parseSemVer :: Text -> Either ParseError SemVer Source

Parse a string as an explicit version, or return an error.

parseSemVerRange :: Text -> Either ParseError SemVerRange Source

Parse a string as a version range, or return an error.

pSemVerRange :: Parser SemVerRange Source

Top-level parser. Parses a semantic version range.

pSemVer :: Parser SemVer Source

Parses a semantic version.

data DistInfo Source

Distribution info from NPM. Tells us the URL and hash of a tarball.

Constructors

DistInfo 

Fields

diUrl :: Text
 
diShasum :: Text
 

getDict :: FromJSON a => Text -> Object -> Parser (HashMap Text a) Source

Gets a hashmap from an object, or otherwise returns an empty hashmap.

_getPackageInfo :: Name -> URI -> NpmFetcher PackageInfo Source

Queries NPM for package information.

getPackageInfo :: Name -> NpmFetcher PackageInfo Source

Same as _getPackageInfo, but caches results for speed.

nixPrefetchSha1 :: URI -> NpmFetcher (Text, FilePath) Source

Returns the SHA1 hash of the result of fetching the URI, and the path in which the tarball is stored.

fetchHttp Source

Arguments

:: Text

Subpath in which to find the package.json.

-> URI

The URI to fetch.

-> NpmFetcher SemVer

The version of the package at that URI.

Fetch a package over HTTP. Return the version of the fetched package, and store the hash.

getDefaultBranch :: Name -> Name -> NpmFetcher Name Source

Queries NPM for package information.

getShaOfBranch Source

Arguments

:: Name

Repo owner

-> Name

Repo name

-> Name

Name of the branch to get

-> NpmFetcher Text

The hash of the branch

Given a github repo and a branch, gets the SHA of the head of that branch

fetchGithub :: URI -> NpmFetcher SemVer Source

Fetch a package from git.

resolveDep :: Name -> SemVerRange -> NpmFetcher SemVer Source

Uses the set of downloaded packages as a cache to avoid unnecessary duplication.

_resolveDep :: Name -> SemVerRange -> NpmFetcher SemVer Source

Resolves a dependency given a name and version range.

getRegistries :: IO [Text] Source

Read NPM registry from env or use default.

getToken :: IO (Maybe Text) Source

Read github auth token from env or use none.

data NixFromNpmOptions Source

Various options we have available for nixfromnpm. As of right now, most of these are unimplemented.