Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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
- 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
- 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 NpmFetcherState = NpmFetcherState {}
- type NpmFetcher = ExceptT EList (StateT NpmFetcherState IO)
- indent :: Text -> NpmFetcher Text
- putStrLnI :: Text -> NpmFetcher ()
- putStrsLnI :: [Text] -> NpmFetcher ()
- putStrI :: Text -> NpmFetcher ()
- putStrsI :: [Text] -> NpmFetcher ()
- addResolvedPkg :: Name -> SemVer -> ResolvedPkg -> NpmFetcher ()
- _defaultCurlArgs :: [Text]
- 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 :: Record (HashMap SemVer NixExpr) -> [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 -> Record (HashMap SemVer NixExpr) -> IO (Record (HashMap SemVer (Either NixExpr ResolvedPkg)))
- _startingSrc :: Text
- _startingExpr :: NixExpr
- callPackage :: NixExpr -> NixExpr
- fixName :: Name -> Name
- toDepName :: Name -> SemVer -> Name
- toDotNix :: SemVer -> Text
- distInfoToNix :: DistInfo -> NixExpr
- metaNotEmpty :: PackageMeta -> Bool
- metaToNix :: PackageMeta -> NixExpr
- resolvedPkgToNix :: ResolvedPkg -> NixExpr
- mkDefault :: Record (HashMap SemVer a) -> NixExpr
- dumpPkgs :: MonadIO m => String -> Record (HashMap SemVer (Either NixExpr ResolvedPkg)) -> m ()
- parseVersion :: String -> IO (Maybe (SemVer, NixExpr))
- findExisting :: String -> IO (Record (HashMap SemVer NixExpr))
- data NixFromNpmOptions = NixFromNpmOptions {
- nfnoPkgName :: Name
- nfnoOutputPath :: Text
- nfnoNoCache :: Bool
- nfnoExtendPaths :: [Text]
- nfnoTest :: Bool
- nfnoRegistries :: [Text]
- nfnoTimeout :: Int
- defaultOptions :: Name -> Text -> NixFromNpmOptions
- dumpPkgNamed :: Bool -> Text -> Text -> IO ()
- 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
A partially specified semantic version. Implicitly defines
a range of acceptable versions, as seen in wildcardToRange
.
data SemVerRange Source
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
data PackageInfo Source
data PackageMeta Source
data VersionInfo Source
VersionInfo | |
|
Distribution info from NPM. Tells us the URL and hash of a tarball.
data ResolvedPkg Source
ResolvedPkg | |
|
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 NpmFetcherState Source
NpmFetcherState | |
|
type NpmFetcher = ExceptT EList (StateT NpmFetcherState IO) 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
_defaultCurlArgs :: [Text] Source
curl :: [Text] -> NpmFetcher Text Source
_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.
:: 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.
:: 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 :: Record (HashMap SemVer NixExpr) -> [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
getPkg :: Name -> Record (HashMap SemVer NixExpr) -> IO (Record (HashMap SemVer (Either NixExpr ResolvedPkg))) Source
callPackage :: NixExpr -> NixExpr Source
distInfoToNix :: DistInfo -> NixExpr Source
metaNotEmpty :: PackageMeta -> Bool Source
metaToNix :: PackageMeta -> NixExpr Source
dumpPkgs :: MonadIO m => String -> Record (HashMap SemVer (Either NixExpr ResolvedPkg)) -> m () Source
data NixFromNpmOptions Source
Various options we have available for nixfromnpm. As of right now, most of these are unimplemented.
NixFromNpmOptions | |
|
defaultOptions :: Name -> Text -> NixFromNpmOptions Source
dumpPkgFromOptions :: NixFromNpmOptions -> IO () Source