Safe Haskell | None |
---|---|
Language | Haskell2010 |
NixFromNpm
- module ClassyPrelude
- module Control.Applicative
- module Control.Exception
- module Control.Exception.ErrorList
- module Control.Monad
- module Control.Monad.Except
- module Control.Monad.Identity
- module Control.Monad.State.Strict
- module Control.Monad.Reader
- module Control.Monad.Trans
- module Data.Char
- module Data.Default
- module Data.HashMap.Strict
- module Data.Either
- module Data.Maybe
- module Data.List
- module Data.String.Utils
- module GHC.Exts
- module Filesystem.Path.CurrentOS
- module Network.URI
- module GHC.IO.Exception
- module System.Directory
- module Text.Render
- module System.FilePath.Posix
- type Name = Text
- type Record = HashMap Name
- type Path = Text
- tuple :: Applicative f => f a -> f b -> f (a, b)
- tuple3 :: Applicative f => f a -> f b -> f c -> f (a, b, c)
- fromRight :: Either a b -> b
- cerror :: [String] -> a
- cerror' :: [Text] -> a
- uriToText :: URI -> Text
- uriToString :: URI -> String
- slash :: URI -> Text -> URI
- putStrsLn :: MonadIO m => [Text] -> m ()
- pathToText :: FilePath -> Text
- putStrs :: MonadIO m => [Text] -> m ()
- dropSuffix :: String -> String -> String
- maybeIf :: Bool -> a -> Maybe a
- grab :: (Hashable k, Eq k) => k -> HashMap k v -> v
- withDir :: String -> IO a -> IO a
- pathToString :: FilePath -> String
- joinBy :: Text -> [Text] -> Text
- mapJoinBy :: Text -> (a -> Text) -> [a] -> Text
- getEnv :: Text -> IO (Maybe Text)
- modifyMap :: (Eq k, Hashable k) => (a -> Maybe b) -> HashMap k a -> HashMap k b
- data NixFromNpmOptions = NixFromNpmOptions {
- nfnoPkgNames :: [Name]
- nfnoPkgPaths :: [Text]
- nfnoOutputPath :: Text
- nfnoNoCache :: Bool
- nfnoExtendPaths :: [Text]
- nfnoTest :: Bool
- nfnoRegistries :: [Text]
- nfnoTimeout :: Int
- nfnoGithubToken :: Maybe Text
- textOption :: Mod OptionFields String -> Parser Text
- pOptions :: Maybe Text -> Parser NixFromNpmOptions
- type SemVer = (Int, Int, Int)
- data Wildcard
- data SemVerRange
- = Eq SemVer
- | Gt SemVer
- | Lt SemVer
- | Geq SemVer
- | Leq SemVer
- | And SemVerRange SemVerRange
- | Or SemVerRange SemVerRange
- renderSV :: SemVer -> Text
- renderSV' :: SemVer -> String
- matches :: SemVerRange -> SemVer -> Bool
- bestMatch :: SemVerRange -> [SemVer] -> Either String SemVer
- wildcardToSemver :: Wildcard -> SemVer
- wildcardToRange :: Wildcard -> SemVerRange
- tildeToRange :: Wildcard -> SemVerRange
- caratToRange :: Wildcard -> SemVerRange
- hyphenatedRange :: Wildcard -> Wildcard -> SemVerRange
- parseSemVer :: Text -> Either ParseError SemVer
- parseSemVerRange :: Text -> Either ParseError SemVerRange
- pSemVerRange :: Parser SemVerRange
- pSemVer :: Parser SemVer
- data GitSource
- data NpmVersionRange
- data PackageInfo = PackageInfo {}
- data PackageMeta = PackageMeta {}
- data VersionInfo = VersionInfo {}
- data DistInfo = DistInfo {}
- data ResolvedPkg = ResolvedPkg {}
- getDict :: FromJSON a => Text -> Object -> Parser (HashMap Text a)
- getObject :: String -> Value -> Parser (HashMap Text Value)
- pUri :: Parser NpmVersionRange
- pGitId :: Parser NpmVersionRange
- pLocalPath :: Parser NpmVersionRange
- pEmptyString :: Parser NpmVersionRange
- pTag :: Parser NpmVersionRange
- pNpmVersionRange :: Parser NpmVersionRange
- parseNpmVersionRange :: Text -> Either ParseError NpmVersionRange
- data FullyDefinedPackage
- data PreExistingPackage
- toFullyDefined :: PreExistingPackage -> FullyDefinedPackage
- type PackageMap pkg = Record (HashMap SemVer pkg)
- mapPM :: (a -> b) -> PackageMap a -> PackageMap b
- data NpmFetcherState = NpmFetcherState {}
- type NpmFetcher = ExceptT EList (StateT NpmFetcherState IO)
- concatDots :: SemVer -> Text
- indent :: Text -> NpmFetcher Text
- putStrLnI :: Text -> NpmFetcher ()
- putStrsLnI :: [Text] -> NpmFetcher ()
- putStrI :: Text -> NpmFetcher ()
- putStrsI :: [Text] -> NpmFetcher ()
- addResolvedPkg :: Name -> SemVer -> ResolvedPkg -> NpmFetcher ()
- curl :: [Text] -> NpmFetcher Text
- _getPackageInfo :: Name -> URI -> NpmFetcher PackageInfo
- getPackageInfo :: Name -> NpmFetcher PackageInfo
- storePackageInfo :: Name -> PackageInfo -> NpmFetcher ()
- toSemVerList :: Record a -> NpmFetcher [(SemVer, a)]
- bestMatchFromRecord :: SemVerRange -> Record a -> NpmFetcher a
- shell :: Sh Text -> NpmFetcher Text
- silentShell :: Sh Text -> NpmFetcher Text
- nixPrefetchSha1 :: URI -> NpmFetcher (Text, FilePath)
- extractVersionInfo :: FilePath -> Text -> NpmFetcher VersionInfo
- fetchHttp :: Text -> URI -> NpmFetcher SemVer
- githubCurl :: Text -> NpmFetcher Value
- getDefaultBranch :: Name -> Name -> NpmFetcher Name
- getShaOfBranch :: Name -> Name -> Name -> NpmFetcher Text
- fetchGithub :: URI -> NpmFetcher SemVer
- resolveNpmVersionRange :: Name -> NpmVersionRange -> NpmFetcher SemVer
- resolveDep :: Name -> SemVerRange -> NpmFetcher SemVer
- startResolving :: Name -> SemVer -> NpmFetcher ()
- finishResolving :: Name -> SemVer -> NpmFetcher ()
- resolveVersionInfo :: VersionInfo -> NpmFetcher SemVer
- _resolveDep :: Name -> SemVerRange -> NpmFetcher SemVer
- resolveByTag :: Name -> Name -> NpmFetcher SemVer
- parseURIs :: [Text] -> [URI]
- startState :: PackageMap PreExistingPackage -> [Text] -> Maybe Text -> NpmFetcherState
- getRegistries :: IO [Text]
- getToken :: IO (Maybe Text)
- runIt :: NpmFetcher a -> IO (a, NpmFetcherState)
- runItWith :: NpmFetcherState -> NpmFetcher a -> IO (a, NpmFetcherState)
- getPkg :: Name -> PackageMap PreExistingPackage -> Maybe Text -> IO (PackageMap FullyDefinedPackage)
- _startingSrc :: String
- _startingExpr :: NExpr
- callPackage :: NExpr -> NExpr
- callPackageWith :: [Binding NExpr] -> NExpr -> NExpr
- callPackageWithRec :: [Binding NExpr] -> NExpr -> NExpr
- fixName :: Name -> Name
- toDepName :: Name -> SemVer -> Name
- toDotNix :: SemVer -> Text
- str :: Text -> NExpr
- distInfoToNix :: DistInfo -> NExpr
- metaNotEmpty :: PackageMeta -> Bool
- metaToNix :: PackageMeta -> NExpr
- resolvedPkgToNix :: ResolvedPkg -> NExpr
- mkDefaultNix :: Record [SemVer] -> Record Path -> NExpr
- takeNewPackages :: PackageMap FullyDefinedPackage -> (PackageMap ResolvedPkg, PackageMap NExpr)
- dumpPkgs :: MonadIO m => String -> PackageMap ResolvedPkg -> PackageMap NExpr -> Record Path -> m ()
- parseVersion :: Name -> Path -> IO (Maybe (SemVer, NExpr))
- findExisting :: Maybe Name -> Path -> IO (PackageMap PreExistingPackage)
- preloadPackages :: Bool -> Path -> Record Path -> IO (PackageMap PreExistingPackage)
- dumpPkgNamed :: Text -> Path -> PackageMap PreExistingPackage -> Record Path -> Maybe Text -> IO ()
- getExtensions :: [Text] -> Record Path
- dumpPkgFromOptions :: NixFromNpmOptions -> IO ()
Documentation
module ClassyPrelude
module Control.Applicative
module Control.Exception
module Control.Exception.ErrorList
module Control.Monad
module Control.Monad.Except
module Control.Monad.Identity
module Control.Monad.State.Strict
module Control.Monad.Reader
module Control.Monad.Trans
module Data.Char
module Data.Default
module Data.HashMap.Strict
module Data.Either
module Data.Maybe
module Data.List
module Data.String.Utils
module GHC.Exts
module Filesystem.Path.CurrentOS
module Network.URI
module GHC.IO.Exception
module System.Directory
module Text.Render
module System.FilePath.Posix
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.
uriToString :: URI -> String Source
slash :: URI -> Text -> URI infixl 6 Source
Appends text to URI with a slash. Ex: foo.com slash
bar == foo.com/bar.
pathToText :: FilePath -> Text Source
dropSuffix :: String -> String -> String Source
pathToString :: FilePath -> String Source
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
|
Instances
textOption :: Mod OptionFields String -> Parser Text Source
A partially specified semantic version. Implicitly defines
a range of acceptable versions, as seen in wildcardToRange
.
data SemVerRange Source
Constructors
Eq SemVer | |
Gt SemVer | |
Lt SemVer | |
Geq SemVer | |
Leq SemVer | |
And SemVerRange SemVerRange | |
Or SemVerRange SemVerRange |
Instances
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.
data NpmVersionRange Source
Constructors
SemVerRange SemVerRange | |
Tag Name | |
NpmUri URI | |
GitId GitSource Name Name (Maybe Name) | |
LocalPath FilePath |
Instances
data PackageInfo Source
Constructors
PackageInfo | |
Fields
|
data VersionInfo Source
Constructors
VersionInfo | |
Fields
|
Instances
Distribution info from NPM. Tells us the URL and hash of a tarball.
data ResolvedPkg Source
Constructors
ResolvedPkg | |
Fields
|
Instances
getDict :: FromJSON a => Text -> Object -> Parser (HashMap Text a) Source
Gets a hashmap from an object, or otherwise returns an empty hashmap.
pUri :: Parser NpmVersionRange Source
pGitId :: Parser NpmVersionRange Source
pLocalPath :: Parser NpmVersionRange Source
pEmptyString :: Parser NpmVersionRange Source
pTag :: Parser NpmVersionRange Source
pNpmVersionRange :: Parser NpmVersionRange Source
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.
Instances
data PreExistingPackage Source
The type of pre-existing packages, which can either come from the output path, or come from an extension
Constructors
FromOutput NExpr | |
FromExtension Name NExpr |
Instances
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.
data NpmFetcherState Source
The state of the NPM fetcher.
Constructors
NpmFetcherState | |
Fields
|
Instances
type NpmFetcher = ExceptT EList (StateT NpmFetcherState IO) Source
concatDots :: SemVer -> Text Source
indent :: Text -> NpmFetcher Text Source
putStrLnI :: Text -> NpmFetcher () Source
putStrsLnI :: [Text] -> NpmFetcher () Source
putStrI :: Text -> NpmFetcher () Source
putStrsI :: [Text] -> NpmFetcher () Source
addResolvedPkg :: Name -> SemVer -> ResolvedPkg -> NpmFetcher () Source
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.
storePackageInfo :: Name -> PackageInfo -> NpmFetcher () Source
toSemVerList :: Record a -> NpmFetcher [(SemVer, a)] Source
bestMatchFromRecord :: SemVerRange -> Record a -> NpmFetcher a Source
silentShell :: Sh Text -> NpmFetcher Text Source
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.
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.
githubCurl :: Text -> NpmFetcher Value Source
getDefaultBranch :: Name -> Name -> NpmFetcher Name Source
Queries NPM for package information.
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.
startResolving :: Name -> SemVer -> NpmFetcher () Source
finishResolving :: Name -> SemVer -> NpmFetcher () Source
_resolveDep :: Name -> SemVerRange -> NpmFetcher SemVer Source
Resolves a dependency given a name and version range.
resolveByTag :: Name -> Name -> NpmFetcher SemVer Source
startState :: PackageMap PreExistingPackage -> [Text] -> Maybe Text -> NpmFetcherState Source
getRegistries :: IO [Text] Source
Read NPM registry from env or use default.
runIt :: NpmFetcher a -> IO (a, NpmFetcherState) Source
runItWith :: NpmFetcherState -> NpmFetcher a -> IO (a, NpmFetcherState) 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. |
callPackage :: NExpr -> NExpr Source
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
.
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.
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.
Arguments
:: Maybe Name | Is |
-> 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.
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.
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.
dumpPkgFromOptions :: NixFromNpmOptions -> IO () Source