Skip to content

Commit

Permalink
Show as "hpack-dhall", empty list of warnings for decodeDhall, NixOS#374
Browse files Browse the repository at this point in the history
.
  • Loading branch information
philderbeast committed Sep 5, 2018
1 parent daad8cc commit d950242
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 4 deletions.
4 changes: 2 additions & 2 deletions src/Distribution/Nixpkgs/Haskell/PackageSourceSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ data CabalGen

instance Show CabalGen where
show CabalGenHpack = "hpack"
show CabalGenDhall = "dhall"
show CabalGenDhall = "hpack-dhall"

getPackage :: Maybe CabalGen
-- ^ Whether and how to regenerate the cabal file.
Expand Down Expand Up @@ -227,7 +227,7 @@ hpackDirectory' :: CabalGen
hpackDirectory' gen optsDecode = do
mPackage <- liftIO $ Hpack.readPackageConfig optsDecode
case mPackage of
Left err -> liftIO $ hPutStrLn stderr ("*** hpack error: " ++ show err ++ ". Exiting.") >> exitFailure
Left err -> liftIO $ hPutStrLn stderr ("*** " ++ show gen ++ " error: " ++ show err ++ ". Exiting.") >> exitFailure
Right r -> do
let hpackOutput = encodeUtf8 $ Hpack.renderPackage [] (Hpack.decodeResultPackage r)
hash = printSHA256 $ digest (digestByName "sha256") hpackOutput
Expand Down
6 changes: 4 additions & 2 deletions src/Hpack/Dhall.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE TupleSections #-}
module Hpack.Dhall where

import Control.Monad.Trans.Except
Expand All @@ -12,11 +13,12 @@ import qualified Dhall.TypeCheck
import qualified Dhall.JSON

-- SEE: https://github.com/sol/hpack-dhall/blob/master/src/Hpack/Dhall.hs
decodeDhall :: FilePath -> IO (Either String Value)
decodeDhall :: FilePath -> IO (Either String ([String], Value))
decodeDhall file = runExceptT $ do
expr <- readInput >>= parseExpr >>= liftIO . Dhall.Import.load
_ <- liftResult $ Dhall.TypeCheck.typeOf expr
liftResult $ Dhall.JSON.dhallToJSON expr
-- NOTE: dhallToJSON returns no warnings hence the empty list of warnings.
liftResult $ ([],) <$> Dhall.JSON.dhallToJSON expr
where
readInput = liftIO (T.readFile file)
parseExpr = liftResult . Dhall.Parser.exprFromText file
Expand Down

0 comments on commit d950242

Please sign in to comment.