{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
module Hpack (
version
, hpack
, hpackResult
, hpackResultWithError
, printResult
, Result(..)
, Status(..)
, defaultOptions
, setProgramName
, setTarget
, setDecode
, setFormatYamlParseError
, getOptions
, Verbose(..)
, Options(..)
, Force(..)
, GenerateHashStrategy(..)
, OutputStrategy(..)
#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]
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
, Options -> OutputStrategy
optionsOutputStrategy :: OutputStrategy
}
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 OutputStrategy
outputStrategy) -> 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
-> OutputStrategy
-> Options
Options DecodeOptions
defaultDecodeOptions {decodeOptionsTarget :: Hash
decodeOptionsTarget = Hash
file} Force
force GenerateHashStrategy
generateHash Bool
toStdout OutputStrategy
outputStrategy)
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 ] [ --canonical ] [ --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
-> OutputStrategy
-> Options
Options DecodeOptions
defaultDecodeOptions Force
NoForce GenerateHashStrategy
PreferNoHash Bool
False OutputStrategy
MinimizeDiffs
setTarget :: FilePath -> Options -> Options
setTarget :: Hash -> Options -> Options
setTarget Hash
target options :: Options
options@Options{Bool
OutputStrategy
Force
DecodeOptions
GenerateHashStrategy
optionsOutputStrategy :: OutputStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsOutputStrategy :: Options -> OutputStrategy
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
OutputStrategy
Force
DecodeOptions
GenerateHashStrategy
optionsOutputStrategy :: OutputStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsOutputStrategy :: Options -> OutputStrategy
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
OutputStrategy
Force
DecodeOptions
GenerateHashStrategy
optionsOutputStrategy :: OutputStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsOutputStrategy :: Options -> OutputStrategy
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}}
setFormatYamlParseError :: (FilePath -> Yaml.ParseException -> String) -> Options -> Options
setFormatYamlParseError :: (Hash -> ParseException -> Hash) -> Options -> Options
setFormatYamlParseError Hash -> ParseException -> Hash
formatYamlParseError options :: Options
options@Options{Bool
OutputStrategy
Force
DecodeOptions
GenerateHashStrategy
optionsOutputStrategy :: OutputStrategy
optionsToStdout :: Bool
optionsGenerateHashStrategy :: GenerateHashStrategy
optionsForce :: Force
optionsDecodeOptions :: DecodeOptions
optionsOutputStrategy :: Options -> OutputStrategy
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 :: NewCabalFile -> ExistingCabalFile -> Status
mkStatus :: NewCabalFile -> ExistingCabalFile -> Status
mkStatus new :: NewCabalFile
new@(CabalFile [Hash]
_ Maybe Version
mNewVersion Maybe Hash
mNewHash [Hash]
_ ()
_) existing :: ExistingCabalFile
existing@(CabalFile [Hash]
_ Maybe Version
mExistingVersion Maybe Hash
_ [Hash]
_ GitConflictMarkers
_)
| NewCabalFile
new NewCabalFile -> ExistingCabalFile -> Bool
`hasSameContent` ExistingCabalFile
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
&& ExistingCabalFile -> Bool
hashMismatch ExistingCabalFile
existing -> Status
ExistingCabalFileWasModifiedManually
| Bool
otherwise -> Status
Generated
hasSameContent :: NewCabalFile -> ExistingCabalFile -> Bool
hasSameContent :: NewCabalFile -> ExistingCabalFile -> Bool
hasSameContent (CabalFile [Hash]
cabalVersionA Maybe Version
_ Maybe Hash
_ [Hash]
a ()) (CabalFile [Hash]
cabalVersionB Maybe Version
_ Maybe Hash
_ [Hash]
b GitConflictMarkers
gitConflictMarkers) =
[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
Bool -> Bool -> Bool
&& GitConflictMarkers
gitConflictMarkers forall a. Eq a => a -> a -> Bool
== GitConflictMarkers
DoesNotHaveGitConflictMarkers
hashMismatch :: ExistingCabalFile -> Bool
hashMismatch :: ExistingCabalFile -> Bool
hashMismatch ExistingCabalFile
cabalFile = case forall a. CabalFile a -> Maybe Hash
cabalFileHash ExistingCabalFile
cabalFile of
Maybe Hash
Nothing -> Bool
False
Just Hash
hash -> forall a. CabalFile a -> a
cabalFileGitConflictMarkers ExistingCabalFile
cabalFile forall a. Eq a => a -> a -> Bool
== GitConflictMarkers
HasGitConflictMarkers Bool -> Bool -> Bool
|| Hash
hash forall a. Eq a => a -> a -> Bool
/= forall a. CabalFile a -> Hash
calculateHash ExistingCabalFile
cabalFile
calculateHash :: CabalFile a -> Hash
calculateHash :: forall a. CabalFile a -> Hash
calculateHash (CabalFile [Hash]
cabalVersion Maybe Version
_ Maybe Hash
_ [Hash]
body a
_) = 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 OutputStrategy
outputStrategy) = 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 ExistingCabalFile
mExistingCabalFile <- Hash -> IO (Maybe ExistingCabalFile)
readCabalFile Hash
cabalFileName
let
newCabalFile :: NewCabalFile
newCabalFile = OutputStrategy
-> GenerateHashStrategy
-> Maybe ExistingCabalFile
-> [Hash]
-> Version
-> Package
-> NewCabalFile
makeCabalFile OutputStrategy
outputStrategy GenerateHashStrategy
generateHashStrategy Maybe ExistingCabalFile
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 (NewCabalFile -> ExistingCabalFile -> Status
mkStatus NewCabalFile
newCabalFile) Maybe ExistingCabalFile
mExistingCabalFile
case Status
status of
Status
Generated -> DecodeOptions -> Bool -> Hash -> NewCabalFile -> IO ()
writeCabalFile DecodeOptions
options Bool
toStdout Hash
cabalFileName NewCabalFile
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 -> NewCabalFile -> IO ()
writeCabalFile :: DecodeOptions -> Bool -> Hash -> NewCabalFile -> IO ()
writeCabalFile DecodeOptions
options Bool
toStdout Hash
name NewCabalFile
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 -> NewCabalFile -> [Hash]
renderCabalFile (DecodeOptions -> Hash
decodeOptionsTarget DecodeOptions
options) NewCabalFile
cabalFile
where
write :: Hash -> IO ()
write = if Bool
toStdout then Hash -> IO ()
Utf8.putStr else Hash -> Hash -> IO ()
Utf8.ensureFile Hash
name
makeCabalFile :: OutputStrategy -> GenerateHashStrategy -> Maybe ExistingCabalFile -> [String] -> Version -> Package -> NewCabalFile
makeCabalFile :: OutputStrategy
-> GenerateHashStrategy
-> Maybe ExistingCabalFile
-> [Hash]
-> Version
-> Package
-> NewCabalFile
makeCabalFile OutputStrategy
outputStrategy GenerateHashStrategy
generateHashStrategy Maybe ExistingCabalFile
mExistingCabalFile [Hash]
cabalVersion Version
v Package
pkg = NewCabalFile
cabalFile
where
hints :: [String]
hints :: [Hash]
hints = case OutputStrategy
outputStrategy of
OutputStrategy
CanonicalOutput -> []
OutputStrategy
MinimizeDiffs -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall a. CabalFile a -> [Hash]
cabalFileContents Maybe ExistingCabalFile
mExistingCabalFile
cabalFile :: NewCabalFile
cabalFile :: NewCabalFile
cabalFile = forall a.
[Hash] -> Maybe Version -> Maybe Hash -> [Hash] -> a -> CabalFile a
CabalFile [Hash]
cabalVersion (forall a. a -> Maybe a
Just Version
v) Maybe Hash
hash [Hash]
body ()
hash :: Maybe Hash
hash :: Maybe Hash
hash
| Maybe ExistingCabalFile -> GenerateHashStrategy -> Bool
shouldGenerateHash Maybe ExistingCabalFile
mExistingCabalFile GenerateHashStrategy
generateHashStrategy = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. CabalFile a -> Hash
calculateHash NewCabalFile
cabalFile
| Bool
otherwise = forall a. Maybe a
Nothing
body :: [String]
body :: [Hash]
body = Hash -> [Hash]
lines forall a b. (a -> b) -> a -> b
$ [Hash] -> Package -> Hash
renderPackage [Hash]
hints Package
pkg
shouldGenerateHash :: Maybe ExistingCabalFile -> GenerateHashStrategy -> Bool
shouldGenerateHash :: Maybe ExistingCabalFile -> GenerateHashStrategy -> Bool
shouldGenerateHash Maybe ExistingCabalFile
mExistingCabalFile GenerateHashStrategy
strategy = case (GenerateHashStrategy
strategy, Maybe ExistingCabalFile
mExistingCabalFile) of
(GenerateHashStrategy
ForceHash, Maybe ExistingCabalFile
_) -> Bool
True
(GenerateHashStrategy
ForceNoHash, Maybe ExistingCabalFile
_) -> Bool
False
(GenerateHashStrategy
PreferHash, Maybe ExistingCabalFile
Nothing) -> Bool
True
(GenerateHashStrategy
PreferNoHash, Maybe ExistingCabalFile
Nothing) -> Bool
False
(GenerateHashStrategy
_, Just CabalFile {cabalFileHash :: forall a. CabalFile a -> Maybe Hash
cabalFileHash = Maybe Hash
Nothing}) -> Bool
False
(GenerateHashStrategy
_, Just CabalFile {cabalFileHash :: forall a. CabalFile a -> Maybe Hash
cabalFileHash = Just Hash
_}) -> Bool
True
renderCabalFile :: FilePath -> NewCabalFile -> [String]
renderCabalFile :: Hash -> NewCabalFile -> [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