{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
module Hpack (
-- | /__NOTE:__/ This module is exposed to allow integration of Hpack into
-- other tools.  It is not meant for general use by end users.  The following
-- caveats apply:
--
-- * The API is undocumented, consult the source instead.
--
-- * The exposed types and functions primarily serve Hpack's own needs, not
-- that of a public API.  Breaking changes can happen as Hpack evolves.
--
-- As an Hpack user you either want to use the @hpack@ executable or a build
-- tool that supports Hpack (e.g. @stack@ or @cabal2nix@).

-- * Version
  version

-- * Running Hpack
, hpack
, hpackResult
, hpackResultWithError
, printResult
, Result(..)
, Status(..)

-- * Options
, defaultOptions
, setProgramName
, setTarget
, setDecode
, setFormatYamlParseError
, getOptions
, Verbose(..)
, Options(..)
, Force(..)
, GenerateHashStrategy(..)

#ifdef TEST
, hpackResultWithVersion
, header
, renderCabalFile
#endif
) where

import           Imports

import           Data.Version (Version)
import qualified Data.Version as Version
import           System.FilePath
import           System.Environment
import           System.Exit
import           System.IO (stderr)
import           Data.Aeson (Value)
import           Data.Maybe

import           Paths_hpack (version)
import           Hpack.Options
import           Hpack.Config
import           Hpack.Error (HpackError, formatHpackError)
import           Hpack.Render
import           Hpack.Util
import           Hpack.Utf8 as Utf8
import           Hpack.CabalFile
import qualified Data.Yaml as Yaml

programVersion :: Maybe Version -> String
programVersion :: Maybe Version -> Hash
programVersion Maybe Version
Nothing = Hash
"hpack"
programVersion (Just Version
v) = Hash
"hpack version " forall a. [a] -> [a] -> [a]
++ Version -> Hash
Version.showVersion Version
v

header :: FilePath -> Maybe Version -> (Maybe Hash) -> [String]
header :: Hash -> Maybe Version -> Maybe Hash -> [Hash]
header Hash
p Maybe Version
v Maybe Hash
hash = [
    Hash
"-- This file has been generated from " forall a. [a] -> [a] -> [a]
++ Hash -> Hash
takeFileName Hash
p forall a. [a] -> [a] -> [a]
++ Hash
" by " forall a. [a] -> [a] -> [a]
++ Maybe Version -> Hash
programVersion Maybe Version
v forall a. [a] -> [a] -> [a]
++ Hash
"."
  , Hash
"--"
  , Hash
"-- see: https://github.com/sol/hpack"
  ] forall a. [a] -> [a] -> [a]
++ case Maybe Hash
hash of
    Just Hash
h -> [Hash
"--" , Hash
"-- hash: " forall a. [a] -> [a] -> [a]
++ Hash
h, Hash
""]
    Maybe Hash
Nothing -> [Hash
""]

data Options = Options {
  Options -> DecodeOptions
optionsDecodeOptions :: DecodeOptions
, Options -> Force
optionsForce :: Force
, Options -> GenerateHashStrategy
optionsGenerateHashStrategy :: GenerateHashStrategy
, Options -> Bool
optionsToStdout :: Bool
}

data GenerateHashStrategy = ForceHash | ForceNoHash | PreferHash | PreferNoHash
  deriving (GenerateHashStrategy -> GenerateHashStrategy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenerateHashStrategy -> GenerateHashStrategy -> Bool
$c/= :: GenerateHashStrategy -> GenerateHashStrategy -> Bool
== :: GenerateHashStrategy -> GenerateHashStrategy -> Bool
$c== :: GenerateHashStrategy -> GenerateHashStrategy -> Bool
Eq, Int -> GenerateHashStrategy -> Hash -> Hash
[GenerateHashStrategy] -> Hash -> Hash
GenerateHashStrategy -> Hash
forall a.
(Int -> a -> Hash -> Hash)
-> (a -> Hash) -> ([a] -> Hash -> Hash) -> Show a
showList :: [GenerateHashStrategy] -> Hash -> Hash
$cshowList :: [GenerateHashStrategy] -> Hash -> Hash
show :: GenerateHashStrategy -> Hash
$cshow :: GenerateHashStrategy -> Hash
showsPrec :: Int -> GenerateHashStrategy -> Hash -> Hash
$cshowsPrec :: Int -> GenerateHashStrategy -> Hash -> Hash
Show)

getOptions :: FilePath -> [String] -> IO (Maybe (Verbose, Options))
getOptions :: Hash -> [Hash] -> IO (Maybe (Verbose, Options))
getOptions Hash
defaultPackageConfig [Hash]
args = do
  ParseResult
result <- Hash -> [Hash] -> IO ParseResult
parseOptions Hash
defaultPackageConfig [Hash]
args
  case ParseResult
result of
    ParseResult
PrintVersion -> do
      Hash -> IO ()
putStrLn (Maybe Version -> Hash
programVersion forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Version
version)
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    ParseResult
PrintNumericVersion -> do
      Hash -> IO ()
putStrLn (Version -> Hash
Version.showVersion Version
version)
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    ParseResult
Help -> do
      IO ()
printHelp
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
    Run (ParseOptions Verbose
verbose Force
force Maybe Bool
hash Bool
toStdout Hash
file) -> do
      let generateHash :: GenerateHashStrategy
generateHash = case Maybe Bool
hash of
            Just Bool
True -> GenerateHashStrategy
ForceHash
            Just Bool
False -> GenerateHashStrategy
ForceNoHash
            Maybe Bool
Nothing -> GenerateHashStrategy
PreferNoHash
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (Verbose
verbose, DecodeOptions -> Force -> GenerateHashStrategy -> Bool -> Options
Options DecodeOptions
defaultDecodeOptions {decodeOptionsTarget :: Hash
decodeOptionsTarget = Hash
file} Force
force GenerateHashStrategy
generateHash Bool
toStdout)
    ParseResult
ParseError -> do
      IO ()
printHelp
      forall a. IO a
exitFailure

printHelp :: IO ()
printHelp :: IO ()
printHelp = do
  Hash
name <- IO Hash
getProgName
  Handle -> Hash -> IO ()
Utf8.hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ [Hash] -> Hash
unlines [
      Hash
"Usage: " forall a. [a] -> [a] -> [a]
++ Hash
name forall a. [a] -> [a] -> [a]
++ Hash
" [ --silent ] [ --force | -f ] [ --[no-]hash ] [ PATH ] [ - ]"
    , Hash
"       " forall a. [a] -> [a] -> [a]
++ Hash
name forall a. [a] -> [a] -> [a]
++ Hash
" --version"
    , Hash
"       " forall a. [a] -> [a] -> [a]
++ Hash
name forall a. [a] -> [a] -> [a]
++ Hash
" --numeric-version"
    , Hash
"       " forall a. [a] -> [a] -> [a]
++ Hash
name forall a. [a] -> [a] -> [a]
++ Hash
" --help"
    ]

hpack :: Verbose -> Options -> IO ()
hpack :: Verbose -> Options -> IO ()
hpack Verbose
verbose Options
options = Options -> IO Result
hpackResult Options
options forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Verbose -> Result -> IO ()
printResult Verbose
verbose

defaultOptions :: Options
defaultOptions :: Options
defaultOptions = DecodeOptions -> Force -> GenerateHashStrategy -> Bool -> Options
Options DecodeOptions
defaultDecodeOptions Force
NoForce GenerateHashStrategy
PreferNoHash Bool
False

setTarget :: FilePath -> Options -> Options
setTarget :: Hash -> Options -> Options
setTarget Hash
target options :: Options
options@Options{Bool
Force
DecodeOptions
GenerateHashStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsToStdout :: Options -> Bool
optionsGenerateHashStrategy :: Options -> GenerateHashStrategy
optionsForce :: Options -> Force
optionsDecodeOptions :: Options -> DecodeOptions
..} =
  Options
options {optionsDecodeOptions :: DecodeOptions
optionsDecodeOptions = DecodeOptions
optionsDecodeOptions {decodeOptionsTarget :: Hash
decodeOptionsTarget = Hash
target}}

setProgramName :: ProgramName -> Options -> Options
setProgramName :: ProgramName -> Options -> Options
setProgramName ProgramName
name options :: Options
options@Options{Bool
Force
DecodeOptions
GenerateHashStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsToStdout :: Options -> Bool
optionsGenerateHashStrategy :: Options -> GenerateHashStrategy
optionsForce :: Options -> Force
optionsDecodeOptions :: Options -> DecodeOptions
..} =
  Options
options {optionsDecodeOptions :: DecodeOptions
optionsDecodeOptions = DecodeOptions
optionsDecodeOptions {decodeOptionsProgramName :: ProgramName
decodeOptionsProgramName = ProgramName
name}}

setDecode :: (FilePath -> IO (Either String ([String], Value))) -> Options -> Options
setDecode :: (Hash -> IO (Either Hash ([Hash], Value))) -> Options -> Options
setDecode Hash -> IO (Either Hash ([Hash], Value))
decode options :: Options
options@Options{Bool
Force
DecodeOptions
GenerateHashStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsToStdout :: Options -> Bool
optionsGenerateHashStrategy :: Options -> GenerateHashStrategy
optionsForce :: Options -> Force
optionsDecodeOptions :: Options -> DecodeOptions
..} =
  Options
options {optionsDecodeOptions :: DecodeOptions
optionsDecodeOptions = DecodeOptions
optionsDecodeOptions {decodeOptionsDecode :: Hash -> IO (Either Hash ([Hash], Value))
decodeOptionsDecode = Hash -> IO (Either Hash ([Hash], Value))
decode}}

-- | This is used to format any `Yaml.ParseException`s encountered during
-- decoding of <https://github.com/sol/hpack#defaults defaults>.
--
-- Note that:
--
-- 1. This is not used to format `Yaml.ParseException`s encountered during
-- decoding of the main @package.yaml@.  To customize this you have to set a
-- custom decode function.
--
-- 2. Some of the constructors of `Yaml.ParseException` are never produced by
-- Hpack (e.g. `Yaml.AesonException` as Hpack uses it's own mechanism to decode
-- `Yaml.Value`s).
--
-- Example:
--
-- @
-- example :: IO (Either `HpackError` `Result`)
-- example = `hpackResultWithError` options
--   where
--     options :: `Options`
--     options = setCustomYamlParseErrorFormat format `defaultOptions`
--
--     format :: FilePath -> `Yaml.ParseException` -> String
--     format file err = file ++ ": " ++ displayException err
--
-- setCustomYamlParseErrorFormat :: (FilePath -> `Yaml.ParseException` -> String) -> `Options` -> `Options`
-- setCustomYamlParseErrorFormat format = `setDecode` decode >>> `setFormatYamlParseError` format
--   where
--     decode :: FilePath -> IO (Either String ([String], Value))
--     decode file = first (format file) \<$> `Hpack.Yaml.decodeYamlWithParseError` file
-- @
setFormatYamlParseError :: (FilePath -> Yaml.ParseException -> String) -> Options -> Options
setFormatYamlParseError :: (Hash -> ParseException -> Hash) -> Options -> Options
setFormatYamlParseError Hash -> ParseException -> Hash
formatYamlParseError options :: Options
options@Options{Bool
Force
DecodeOptions
GenerateHashStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsToStdout :: Options -> Bool
optionsGenerateHashStrategy :: Options -> GenerateHashStrategy
optionsForce :: Options -> Force
optionsDecodeOptions :: Options -> DecodeOptions
..} =
  Options
options {optionsDecodeOptions :: DecodeOptions
optionsDecodeOptions = DecodeOptions
optionsDecodeOptions {decodeOptionsFormatYamlParseError :: Hash -> ParseException -> Hash
decodeOptionsFormatYamlParseError = Hash -> ParseException -> Hash
formatYamlParseError}}

data Result = Result {
  Result -> [Hash]
resultWarnings :: [String]
, Result -> Hash
resultCabalFile :: String
, Result -> Status
resultStatus :: Status
} deriving (Result -> Result -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
Eq, Int -> Result -> Hash -> Hash
[Result] -> Hash -> Hash
Result -> Hash
forall a.
(Int -> a -> Hash -> Hash)
-> (a -> Hash) -> ([a] -> Hash -> Hash) -> Show a
showList :: [Result] -> Hash -> Hash
$cshowList :: [Result] -> Hash -> Hash
show :: Result -> Hash
$cshow :: Result -> Hash
showsPrec :: Int -> Result -> Hash -> Hash
$cshowsPrec :: Int -> Result -> Hash -> Hash
Show)

data Status =
    Generated
  | ExistingCabalFileWasModifiedManually
  | AlreadyGeneratedByNewerHpack
  | OutputUnchanged
  deriving (Status -> Status -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq, Int -> Status -> Hash -> Hash
[Status] -> Hash -> Hash
Status -> Hash
forall a.
(Int -> a -> Hash -> Hash)
-> (a -> Hash) -> ([a] -> Hash -> Hash) -> Show a
showList :: [Status] -> Hash -> Hash
$cshowList :: [Status] -> Hash -> Hash
show :: Status -> Hash
$cshow :: Status -> Hash
showsPrec :: Int -> Status -> Hash -> Hash
$cshowsPrec :: Int -> Status -> Hash -> Hash
Show)

printResult :: Verbose -> Result -> IO ()
printResult :: Verbose -> Result -> IO ()
printResult Verbose
verbose Result
r = do
  [Hash] -> IO ()
printWarnings (Result -> [Hash]
resultWarnings Result
r)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbose
verbose forall a. Eq a => a -> a -> Bool
== Verbose
Verbose) forall a b. (a -> b) -> a -> b
$ Hash -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$
    case Result -> Status
resultStatus Result
r of
      Status
Generated -> Hash
"generated " forall a. [a] -> [a] -> [a]
++ Result -> Hash
resultCabalFile Result
r
      Status
OutputUnchanged -> Result -> Hash
resultCabalFile Result
r forall a. [a] -> [a] -> [a]
++ Hash
" is up-to-date"
      Status
AlreadyGeneratedByNewerHpack -> Result -> Hash
resultCabalFile Result
r forall a. [a] -> [a] -> [a]
++ Hash
" was generated with a newer version of hpack, please upgrade and try again."
      Status
ExistingCabalFileWasModifiedManually -> Result -> Hash
resultCabalFile Result
r forall a. [a] -> [a] -> [a]
++ Hash
" was modified manually, please use --force to overwrite."
  case Result -> Status
resultStatus Result
r of
      Status
Generated -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
      Status
OutputUnchanged -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
      Status
AlreadyGeneratedByNewerHpack -> forall a. IO a
exitFailure
      Status
ExistingCabalFileWasModifiedManually -> forall a. IO a
exitFailure

printWarnings :: [String] -> IO ()
printWarnings :: [Hash] -> IO ()
printWarnings = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall a b. (a -> b) -> a -> b
$ Handle -> Hash -> IO ()
Utf8.hPutStrLn Handle
stderr forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Hash
"WARNING: " forall a. [a] -> [a] -> [a]
++)

mkStatus :: CabalFile -> CabalFile -> Status
mkStatus :: CabalFile -> CabalFile -> Status
mkStatus new :: CabalFile
new@(CabalFile [Hash]
_ Maybe Version
mNewVersion Maybe Hash
mNewHash [Hash]
_) existing :: CabalFile
existing@(CabalFile [Hash]
_ Maybe Version
mExistingVersion Maybe Hash
_ [Hash]
_)
  | CabalFile
new CabalFile -> CabalFile -> Bool
`hasSameContent` CabalFile
existing = Status
OutputUnchanged
  | Bool
otherwise = case Maybe Version
mExistingVersion of
      Maybe Version
Nothing -> Status
ExistingCabalFileWasModifiedManually
      Just Version
_
        | Maybe Version
mNewVersion forall a. Ord a => a -> a -> Bool
< Maybe Version
mExistingVersion -> Status
AlreadyGeneratedByNewerHpack
        | forall a. Maybe a -> Bool
isJust Maybe Hash
mNewHash Bool -> Bool -> Bool
&& CabalFile -> Bool
hashMismatch CabalFile
existing -> Status
ExistingCabalFileWasModifiedManually
        | Bool
otherwise -> Status
Generated

hasSameContent :: CabalFile -> CabalFile -> Bool
hasSameContent :: CabalFile -> CabalFile -> Bool
hasSameContent (CabalFile [Hash]
cabalVersionA Maybe Version
_ Maybe Hash
_ [Hash]
a) (CabalFile [Hash]
cabalVersionB Maybe Version
_ Maybe Hash
_ [Hash]
b) = [Hash]
cabalVersionA forall a. Eq a => a -> a -> Bool
== [Hash]
cabalVersionB Bool -> Bool -> Bool
&& [Hash]
a forall a. Eq a => a -> a -> Bool
== [Hash]
b

hashMismatch :: CabalFile -> Bool
hashMismatch :: CabalFile -> Bool
hashMismatch CabalFile
cabalFile = case CabalFile -> Maybe Hash
cabalFileHash CabalFile
cabalFile of
  Maybe Hash
Nothing -> Bool
False
  Just Hash
hash -> Hash
hash forall a. Eq a => a -> a -> Bool
/= CabalFile -> Hash
calculateHash CabalFile
cabalFile

calculateHash :: CabalFile -> Hash
calculateHash :: CabalFile -> Hash
calculateHash (CabalFile [Hash]
cabalVersion Maybe Version
_ Maybe Hash
_ [Hash]
body) = Hash -> Hash
sha256 ([Hash] -> Hash
unlines forall a b. (a -> b) -> a -> b
$ [Hash]
cabalVersion forall a. [a] -> [a] -> [a]
++ [Hash]
body)

hpackResult :: Options -> IO Result
hpackResult :: Options -> IO Result
hpackResult Options
opts = Options -> IO (Either HpackError Result)
hpackResultWithError Options
opts forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Hash -> IO a
die forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProgramName -> HpackError -> Hash
formatHpackError ProgramName
programName) forall (m :: * -> *) a. Monad m => a -> m a
return
  where
    programName :: ProgramName
programName = DecodeOptions -> ProgramName
decodeOptionsProgramName (Options -> DecodeOptions
optionsDecodeOptions Options
opts)

hpackResultWithError :: Options -> IO (Either HpackError Result)
hpackResultWithError :: Options -> IO (Either HpackError Result)
hpackResultWithError = Version -> Options -> IO (Either HpackError Result)
hpackResultWithVersion Version
version

hpackResultWithVersion :: Version -> Options -> IO (Either HpackError Result)
hpackResultWithVersion :: Version -> Options -> IO (Either HpackError Result)
hpackResultWithVersion Version
v (Options DecodeOptions
options Force
force GenerateHashStrategy
generateHashStrategy Bool
toStdout) = do
  DecodeOptions -> IO (Either HpackError DecodeResult)
readPackageConfigWithError DecodeOptions
options forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ case
    Right (DecodeResult Package
pkg (Hash -> [Hash]
lines -> [Hash]
cabalVersion) Hash
cabalFileName [Hash]
warnings) -> do
      Maybe CabalFile
mExistingCabalFile <- Hash -> IO (Maybe CabalFile)
readCabalFile Hash
cabalFileName
      let
        newCabalFile :: CabalFile
newCabalFile = GenerateHashStrategy
-> Maybe CabalFile -> [Hash] -> Version -> Package -> CabalFile
makeCabalFile GenerateHashStrategy
generateHashStrategy Maybe CabalFile
mExistingCabalFile [Hash]
cabalVersion Version
v Package
pkg

        status :: Status
status = case Force
force of
          Force
Force -> Status
Generated
          Force
NoForce -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe Status
Generated (CabalFile -> CabalFile -> Status
mkStatus CabalFile
newCabalFile) Maybe CabalFile
mExistingCabalFile

      case Status
status of
        Status
Generated -> DecodeOptions -> Bool -> Hash -> CabalFile -> IO ()
writeCabalFile DecodeOptions
options Bool
toStdout Hash
cabalFileName CabalFile
newCabalFile
        Status
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right Result {
        resultWarnings :: [Hash]
resultWarnings = [Hash]
warnings
      , resultCabalFile :: Hash
resultCabalFile = Hash
cabalFileName
      , resultStatus :: Status
resultStatus = Status
status
      }
    Left HpackError
err -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left HpackError
err

writeCabalFile :: DecodeOptions -> Bool -> FilePath -> CabalFile -> IO ()
writeCabalFile :: DecodeOptions -> Bool -> Hash -> CabalFile -> IO ()
writeCabalFile DecodeOptions
options Bool
toStdout Hash
name CabalFile
cabalFile = do
  Hash -> IO ()
write forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Hash] -> Hash
unlines forall a b. (a -> b) -> a -> b
$ Hash -> CabalFile -> [Hash]
renderCabalFile (DecodeOptions -> Hash
decodeOptionsTarget DecodeOptions
options) CabalFile
cabalFile
  where
    write :: Hash -> IO ()
write = if Bool
toStdout then Hash -> IO ()
Utf8.putStr else Hash -> Hash -> IO ()
Utf8.writeFile Hash
name

makeCabalFile :: GenerateHashStrategy -> Maybe CabalFile -> [String] -> Version -> Package -> CabalFile
makeCabalFile :: GenerateHashStrategy
-> Maybe CabalFile -> [Hash] -> Version -> Package -> CabalFile
makeCabalFile GenerateHashStrategy
strategy Maybe CabalFile
mExistingCabalFile [Hash]
cabalVersion Version
v Package
pkg = CabalFile
cabalFile
  where
    cabalFile :: CabalFile
cabalFile = [Hash] -> Maybe Version -> Maybe Hash -> [Hash] -> CabalFile
CabalFile [Hash]
cabalVersion (forall a. a -> Maybe a
Just Version
v) Maybe Hash
hash [Hash]
body

    hash :: Maybe Hash
hash
      | Maybe CabalFile -> GenerateHashStrategy -> Bool
shouldGenerateHash Maybe CabalFile
mExistingCabalFile GenerateHashStrategy
strategy = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ CabalFile -> Hash
calculateHash CabalFile
cabalFile
      | Bool
otherwise = forall a. Maybe a
Nothing

    body :: [Hash]
body = Hash -> [Hash]
lines forall a b. (a -> b) -> a -> b
$ [Hash] -> Package -> Hash
renderPackage (forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] CabalFile -> [Hash]
cabalFileContents Maybe CabalFile
mExistingCabalFile) Package
pkg

shouldGenerateHash :: Maybe CabalFile -> GenerateHashStrategy -> Bool
shouldGenerateHash :: Maybe CabalFile -> GenerateHashStrategy -> Bool
shouldGenerateHash Maybe CabalFile
mExistingCabalFile GenerateHashStrategy
strategy = case (GenerateHashStrategy
strategy, Maybe CabalFile
mExistingCabalFile) of
  (GenerateHashStrategy
ForceHash, Maybe CabalFile
_) -> Bool
True
  (GenerateHashStrategy
ForceNoHash, Maybe CabalFile
_) -> Bool
False
  (GenerateHashStrategy
PreferHash, Maybe CabalFile
Nothing) -> Bool
True
  (GenerateHashStrategy
PreferNoHash, Maybe CabalFile
Nothing) -> Bool
False
  (GenerateHashStrategy
_, Just CabalFile {cabalFileHash :: CabalFile -> Maybe Hash
cabalFileHash = Maybe Hash
Nothing}) -> Bool
False
  (GenerateHashStrategy
_, Just CabalFile {cabalFileHash :: CabalFile -> Maybe Hash
cabalFileHash = Just Hash
_}) -> Bool
True

renderCabalFile :: FilePath -> CabalFile -> [String]
renderCabalFile :: Hash -> CabalFile -> [Hash]
renderCabalFile Hash
file (CabalFile [Hash]
cabalVersion Maybe Version
hpackVersion Maybe Hash
hash [Hash]
body) = [Hash]
cabalVersion forall a. [a] -> [a] -> [a]
++ Hash -> Maybe Version -> Maybe Hash -> [Hash]
header Hash
file Maybe Version
hpackVersion Maybe Hash
hash forall a. [a] -> [a] -> [a]
++ [Hash]
body