Skip to content

Commit

Permalink
Support hnix-0.6.0 (#154)
Browse files Browse the repository at this point in the history
  • Loading branch information
j6carey authored and ixmatus committed Mar 21, 2019
1 parent 7dc160c commit 4ab773c
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 5 deletions.
34 changes: 30 additions & 4 deletions src/NixFromNpm/Conversion/ToDisk.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
Expand Down Expand Up @@ -27,6 +28,9 @@ import NixFromNpm.Common
import Nix.Expr (NExpr)
import Nix.Parser (Result(..), parseNixFile)
import Nix.Pretty (prettyNix)
#if MIN_VERSION_hnix(0,6,0)
import Nix.Render (MonadFile)
#endif
import NixFromNpm.Conversion.ToNix (ResolvedPkg(..),
toDotNix,
writeNix,
Expand Down Expand Up @@ -58,7 +62,12 @@ takeNewPackages startingRec = do

-- | Given the path to a package, finds all of the .nix files which parse
-- correctly.
parseVersionFiles :: MonadIO io
parseVersionFiles ::
#if MIN_VERSION_hnix(0,6,0)
(MonadIO io, MonadFile io)
#else
MonadIO io
#endif
=> Bool -- ^ Verbose output.
-> PackageName -- ^ Name of the package this is a version of.
-> FilePath -- ^ Folder with .nix files for this package.
Expand All @@ -83,7 +92,13 @@ parseVersionFiles verbose pkgName folder = do

-- | Given a directory containing npm nix expressions, parse it into a
-- packagemap of parsed nix expressions.
scanNodePackagesDir :: MonadIO io => Bool -> FilePath -> io (PackageMap NExpr)
scanNodePackagesDir ::
#if MIN_VERSION_hnix(0,6,0)
(MonadIO io, MonadFile io)
#else
MonadIO io
#endif
=> Bool -> FilePath -> io (PackageMap NExpr)
scanNodePackagesDir verbose nodePackagesDir = pmConcat <$> do
forItemsInDir nodePackagesDir $ \dir -> do
doesDirectoryExist dir >>= \case
Expand All @@ -100,7 +115,13 @@ scanNodePackagesDir verbose nodePackagesDir = pmConcat <$> do

-- | Given a nodePackages folder, create a default.nix which contains all
-- of the packages in that folder.
writeNodePackagesNix :: MonadIO io => Bool -> FilePath -> io ()
writeNodePackagesNix ::
#if MIN_VERSION_hnix(0,6,0)
(MonadIO io, MonadFile io)
#else
MonadIO io
#endif
=> Bool -> FilePath -> io ()
writeNodePackagesNix verbose path' = do
path <- absPath path'
whenM (not <$> doesDirectoryExist (path </> nodePackagesDir)) $ do
Expand All @@ -112,7 +133,12 @@ writeNodePackagesNix verbose path' = do

-- | Given the path to a file possibly containing nix expressions, finds all
-- expressions findable at that path and returns a map of them.
findExisting :: (MonadBaseControl IO io, MonadIO io)
findExisting ::
#if MIN_VERSION_hnix(0,6,0)
(MonadBaseControl IO io, MonadIO io, MonadFile io)
#else
(MonadBaseControl IO io, MonadIO io)
#endif
=> Bool -- ^ Verbose
-> FilePath -- ^ The path to search.
-> io (PackageMap PreExistingPackage)
Expand Down
12 changes: 11 additions & 1 deletion src/NixFromNpm/Merge.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,14 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
module NixFromNpm.Merge where

#if MIN_VERSION_hnix(0,6,0)
import Nix.Render (MonadFile)
#endif

import NixFromNpm.Common
import NixFromNpm.Conversion.ToDisk (writeNodePackagesNix)
import NixFromNpm.Conversion.ToNix (nodePackagesDir)
Expand All @@ -16,7 +21,12 @@ newtype Dest = Dest FilePath

-- | Merges one folder containing expressions into another. After the merge,
-- generates a new nodePackages/default.nix in the target directory.
mergeInto :: (MonadIO io, MonadBaseControl IO io)
mergeInto ::
#if MIN_VERSION_hnix(0,6,0)
(MonadIO io, MonadBaseControl IO io, MonadFile io)
#else
(MonadIO io, MonadBaseControl IO io)
#endif
=> MergeType -- ^ If DryRun, it will just report what it would have
-- otherwise done.
-> Source -- ^ Source path, containing store objects
Expand Down
9 changes: 9 additions & 0 deletions src/NixFromNpm/Npm/Resolve.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
module NixFromNpm.Npm.Resolve where

--------------------------------------------------------------------------
Expand Down Expand Up @@ -33,6 +35,9 @@ import Shelly (shelly, run, run_, Sh, errExit, lastExitCode, lastStderr,
silently)
import Network.URI (escapeURIString, isUnreserved)
import Nix.Expr
#if MIN_VERSION_hnix(0,6,0)
import Nix.Render (MonadFile)
#endif
import Data.Digest.Pure.SHA (sha256, showDigest)
import Data.SemVer

Expand Down Expand Up @@ -128,6 +133,10 @@ data BrokenPackageReport = BrokenPackageReport {
-- | The monad for fetching from NPM.
type NpmFetcher = RWST NpmFetcherSettings () NpmFetcherState IO

#if MIN_VERSION_hnix(0,6,0)
instance MonadFile NpmFetcher
#endif

-- | Wraps the curl function to fetch from HTTP, setting some headers and
-- telling it to follow redirects.
npmGetHttp :: URI -- ^ URI to hit
Expand Down

0 comments on commit 4ab773c

Please sign in to comment.