Skip to content

Commit

Permalink
make compatible with new versions of upstream libs
Browse files Browse the repository at this point in the history
  • Loading branch information
Allen Nelson committed Sep 1, 2017
1 parent fb8655b commit 517c22c
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 12 deletions.
21 changes: 15 additions & 6 deletions src/Filesystem/Path/Wrappers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Filesystem.Path.Wrappers where

import ClassyPrelude hiding (FilePath, unpack, (</>), readFile)
import ClassyPrelude hiding (FilePath, unpack, (</>), readFile, readFileUtf8,
writeFile, writeFileUtf8)
import qualified ClassyPrelude as CP
import Data.Text hiding (map)
import qualified Data.Text as T
Expand Down Expand Up @@ -36,16 +37,24 @@ getDataFileName :: MonadIO io => FilePath -> io FilePath
getDataFileName = map decodeString . generalize Paths.getDataFileName

-- | Write some stuff to disk.
writeFile :: MonadIO io => FilePath -> Text -> io ()
writeFile path = CP.writeFileUtf8 (pathToString path)
writeFile :: MonadIO io => FilePath -> ByteString -> io ()
writeFile path = CP.writeFile (pathToString path)

-- | Write some stuff to disk.
writeFileUtf8 :: MonadIO io => FilePath -> Text -> io ()
writeFileUtf8 path = CP.writeFileUtf8 (pathToString path)

-- | Read a file from disk.
readFile :: MonadIO io => FilePath -> io ByteString
readFile = generalize CP.readFile

-- | Read a file from disk.
readFile :: MonadIO io => FilePath -> io Text
readFile = generalize CP.readFileUtf8
readFileUtf8 :: MonadIO io => FilePath -> io Text
readFileUtf8 = generalize CP.readFileUtf8

-- | Read a data file, as included by cabal.
readDataFile :: MonadIO io => FilePath -> io Text
readDataFile = getDataFileName >=> readFile
readDataFile = getDataFileName >=> readFileUtf8

-- | Create a symbolic link at `path2` pointing to `path1`.
createSymbolicLink :: (MonadIO io) => FilePath -> FilePath -> io ()
Expand Down
8 changes: 5 additions & 3 deletions src/NixFromNpm/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ module NixFromNpm.Common (
module Text.Printf,
module Control.Monad.Trans.Control,
module System.Console.ANSI,
Name, AuthToken, Record, (//),
Name, AuthToken, Record, (//), (<>),
uriToText, uriToString, putStrsLn, putStrs, dropSuffix, maybeIf, failC,
errorC, joinBy, mapJoinBy, getEnv, modifyMap, unsafeParseURI,
parseURIText, withColor, withUL, warn, warns, assert, fatal, fatalC,
Expand All @@ -45,10 +45,11 @@ import ClassyPrelude hiding (assert, asList, find, FilePath, bracket,
maximum, maximumBy, (</>), (<>),
minimum, try, stripPrefix, ioError,
mapM_, sequence_, foldM, forM_, throw, throwIO,
filterM, replicateM, writeFile, readFile)
filterM, replicateM, writeFile, readFile,
writeFileUtf8, readFileUtf8)
import Control.Exception (throw)
import qualified Prelude as P
import Control.Monad.RWS.Strict hiding (Any)
import Control.Monad.RWS.Strict hiding (Any, (<>))
import Control.Monad (when)
import Control.Monad.Trans (MonadIO(..), lift)
import Control.Monad.Reader (ReaderT(..), MonadReader(..), (<=<), (>=>), ask,
Expand All @@ -70,6 +71,7 @@ import qualified Data.HashMap.Strict as H
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe (fromJust, isJust, isNothing)
import Data.Monoid ((<>))
import Data.Either (isRight, isLeft)
import Data.String.Utils hiding (join)
import qualified Data.Text as T
Expand Down
4 changes: 2 additions & 2 deletions src/NixFromNpm/Conversion/ToDisk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ parseVersionFiles verbose pkgName folder = do
case parseSemVer (pathToText versionTxt) of
_ | ext /= Just "nix" -> return Nothing -- not a nix file
Left _ -> return Nothing -- not a version file
Right version -> parseNixString . T.unpack <$> readFile path >>= \case
Right version -> parseNixString . unpack <$> readFileUtf8 path >>= \case
Failure err -> do
putStrsLn ["Warning: expression for ", tshow pkgName, " version ",
pathToText versionTxt, " failed to parse:\n", tshow err]
Expand Down Expand Up @@ -170,7 +170,7 @@ initializeOutput = do
putStrsLn ["Initializing ", pathToText outputPath]
createDirectoryIfMissing outputPath
createDirectoryIfMissing (outputPath </> nodePackagesDir)
writeFile (outputPath </> ".nixfromnpm-version") $ tshow version
writeFileUtf8 (outputPath </> ".nixfromnpm-version") $ tshow version
case H.keys extensions of
[] -> do -- Then we are creating a new root.
unlessExists defaultNixPath $
Expand Down
2 changes: 1 addition & 1 deletion src/NixFromNpm/Conversion/ToNix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,7 +95,7 @@ toNixExpr name (Broken reason) = "brokenPackage" @@ mkNonRecSet

-- | Write a nix expression pretty-printed to a file.
writeNix :: MonadIO io => FilePath -> NExpr -> io ()
writeNix path = writeFile path . T.pack . (<> "\n") . show . prettyNix
writeNix path = writeFileUtf8 path . (<> "\n") . tshow . prettyNix

-- | Gets the .nix filename of a semver. E.g. (0, 1, 2) -> 0.1.2.nix
toDotNix :: SemVer -> FilePath
Expand Down

0 comments on commit 517c22c

Please sign in to comment.