nixfromnpm-0.2.1: 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.

type Path = Text Source

Indicates that the text is some path.

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

getEnv :: Text -> IO (Maybe Text) Source

Reads an environment variable.

modifyMap :: (Eq k, Hashable k) => (a -> Maybe b) -> HashMap k a -> HashMap k b Source

Create a hashmap by applying a test to everything in the existing map.

data NixFromNpmOptions Source

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

Constructors

NixFromNpmOptions 

Fields

nfnoPkgNames :: [Name]

Names of packages to build.

nfnoPkgPaths :: [Text]

Paths to package.jsons to build.

nfnoOutputPath :: Text

Path to output built expressions to.

nfnoNoCache :: Bool

Build all expressions from scratch.

nfnoExtendPaths :: [Text]

Extend existing expressions.

nfnoTest :: Bool

Fetch only; don't write expressions.

nfnoRegistries :: [Text]

List of registries to query.

nfnoTimeout :: Int

Number of seconds after which to timeout.

nfnoGithubToken :: Maybe Text

Github authentication token.

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.

data FullyDefinedPackage Source

Things which can be converted into nix expressions: either they are actual nix expressions themselves (which can be either existing in the output, or existing in an extension), or they are new packages which we have discovered.

data PreExistingPackage Source

The type of pre-existing packages, which can either come from the output path, or come from an extension

type PackageMap pkg = Record (HashMap SemVer pkg) Source

We use this data structure a lot: a mapping of package names to a mapping of versions to fully defined packages.

mapPM :: (a -> b) -> PackageMap a -> PackageMap b Source

Map a function across a PackageMap.

curl :: [Text] -> NpmFetcher Text Source

Performs a curl query and returns whatever that query returns.

_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.

getPkg Source

Arguments

:: Name

Name of package to get.

-> PackageMap PreExistingPackage

Set of pre-existing packages.

-> Maybe Text

A possible github token.

-> IO (PackageMap FullyDefinedPackage)

Set of fully defined packages.

fixName :: Name -> Name Source

Turns a string into one that can be used as an identifier.

toDepName :: Name -> SemVer -> Name Source

Converts a package name and semver into an identifier.

toDotNix :: SemVer -> Text Source

Gets the .nix filename of a semver. E.g. (0, 1, 2) -> 0.1.2.nix

str :: Text -> NExpr Source

Creates a doublequoted string from some text.

distInfoToNix :: DistInfo -> NExpr Source

Converts distinfo into a nix fetchurl call.

metaNotEmpty :: PackageMeta -> Bool Source

Tests if there is information in the package meta.

metaToNix :: PackageMeta -> NExpr Source

Converts package meta to a nix expression.

resolvedPkgToNix :: ResolvedPkg -> NExpr Source

Converts a resolved package object into a nix expression. The expresion will be a function where the arguments are its dependencies, and its result is a call to buildNodePackage.

mkDefaultNix Source

Arguments

:: Record [SemVer]

Map of names to versions of packages that exist in this library.

-> Record Path

Map of extensions being included.

-> NExpr

A generated nix expression.

Creates the `default.nix` file that is the top-level expression we are generating.

takeNewPackages :: PackageMap FullyDefinedPackage -> (PackageMap ResolvedPkg, PackageMap NExpr) Source

The npm lookup utilities will produce a bunch of fully defined packages. However, the only packages that we want to write are the new ones; that is, the ones that we've discovered and the ones that already exist. This will perform the appropriate filter.

dumpPkgs Source

Arguments

:: MonadIO m 
=> String

Path to output directory.

-> PackageMap ResolvedPkg

New packages being written.

-> PackageMap NExpr

Existing packages to be included in the generated default.nix.

-> Record Path

Libraries being extended.

-> m () 

Actually writes the packages to disk. Takes in the new packages to write, and the names/paths to the libraries being extended.

parseVersion :: Name -> Path -> IO (Maybe (SemVer, NExpr)) Source

Given the path to a package, finds all of the .nix files which parse correctly.

findExisting Source

Arguments

:: Maybe Name

Is Just if this is an extension.

-> Path

The path to search.

-> IO (PackageMap PreExistingPackage)

Mapping of package names to maps of versions to nix expressions.

Given the path to a file possibly containing nix expressions, finds all expressions findable at that path and returns a map of them.

preloadPackages Source

Arguments

:: Bool

Whether to skip the existence check.

-> Path

Output path to search for existing packages.

-> Record Path

Mapping of names of libraries to extend, and paths to those libraries.

-> IO (PackageMap PreExistingPackage) 

Given the output directory and any number of extensions to load, finds any existing packages.

dumpPkgNamed Source

Arguments

:: Text

The name of the package to fetch.

-> Path

The path to output to.

-> PackageMap PreExistingPackage

Set of existing packages.

-> Record Path

Names -> paths of extensions.

-> Maybe Text

Optional github token.

-> IO ()

Writes files to a folder.

Given the name of a package and a place to dump expressions to, generates the expressions needed to build that package.

getExtensions :: [Text] -> Record Path Source

Parse the NAME=PATH extension directives.