Skip to content

Commit

Permalink
wip
Browse files Browse the repository at this point in the history
  • Loading branch information
sol committed Dec 5, 2022
1 parent 7ec449e commit be187b1
Show file tree
Hide file tree
Showing 8 changed files with 143 additions and 87 deletions.
2 changes: 1 addition & 1 deletion .ghci
Original file line number Diff line number Diff line change
@@ -1 +1 @@
:set -XHaskell2010 -fno-warn-incomplete-uni-patterns -DTEST -isrc -itest -i./dist-newstyle/build/x86_64-linux/ghc-9.2.2/hpack-0.34.7/build/autogen/
:set -XHaskell2010 -fno-warn-incomplete-uni-patterns -DTEST -isrc -itest -i./dist-newstyle/build/x86_64-linux/ghc-9.4.2/hpack-0.35.0/build/autogen/
4 changes: 3 additions & 1 deletion hpack.cabal

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

57 changes: 30 additions & 27 deletions src/Hpack.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,13 +20,13 @@ module Hpack (
-- * Running Hpack
, hpack
, hpackResult
, hpackResultWithError
, printResult
, Result(..)
, Status(..)

-- * Options
, defaultOptions
, setProgramName
, setTarget
, setDecode
, getOptions
Expand Down Expand Up @@ -56,14 +56,15 @@ import Data.Maybe
import Paths_hpack (version)
import Hpack.Options
import Hpack.Config
import Hpack.Error (HpackError, renderHpackError, hpackProgName)
import Hpack.Render
import Hpack.Util
import Hpack.Utf8 as Utf8
import Hpack.CabalFile

programVersion :: Maybe Version -> String
programVersion Nothing = "hpack"
programVersion (Just v) = "hpack version " ++ Version.showVersion v
programVersion Nothing = unProgramName hpackProgName
programVersion (Just v) = unProgramName hpackProgName ++ " version " ++ Version.showVersion v

header :: FilePath -> Maybe Version -> (Maybe Hash) -> [String]
header p v hash = [
Expand Down Expand Up @@ -127,10 +128,6 @@ setTarget :: FilePath -> Options -> Options
setTarget target options@Options{..} =
options {optionsDecodeOptions = optionsDecodeOptions {decodeOptionsTarget = target}}

setProgramName :: ProgramName -> Options -> Options
setProgramName name options@Options{..} =
options {optionsDecodeOptions = optionsDecodeOptions {decodeOptionsProgramName = name}}

setDecode :: (FilePath -> IO (Either String ([String], Value))) -> Options -> Options
setDecode decode options@Options{..} =
options {optionsDecodeOptions = optionsDecodeOptions {decodeOptionsDecode = decode}}
Expand Down Expand Up @@ -188,28 +185,34 @@ calculateHash :: CabalFile -> Hash
calculateHash (CabalFile cabalVersion _ _ body) = sha256 (unlines $ cabalVersion ++ body)

hpackResult :: Options -> IO Result
hpackResult = hpackResultWithVersion version
hpackResult opts = hpackResultWithError opts >>= either (die . renderHpackError hpackProgName) return

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

hpackResultWithVersion :: Version -> Options -> IO Result
hpackResultWithVersion :: Version -> Options -> IO (Either HpackError Result)
hpackResultWithVersion v (Options options force generateHashStrategy toStdout) = do
DecodeResult pkg (lines -> cabalVersion) cabalFileName warnings <- readPackageConfig options >>= either die return
mExistingCabalFile <- readCabalFile cabalFileName
let
newCabalFile = makeCabalFile generateHashStrategy mExistingCabalFile cabalVersion v pkg

status = case force of
Force -> Generated
NoForce -> maybe Generated (mkStatus newCabalFile) mExistingCabalFile

case status of
Generated -> writeCabalFile options toStdout cabalFileName newCabalFile
_ -> return ()

return Result {
resultWarnings = warnings
, resultCabalFile = cabalFileName
, resultStatus = status
}
eres <- readPackageConfigWithError options
case eres of
Right (DecodeResult pkg (lines -> cabalVersion) cabalFileName warnings) -> do
mExistingCabalFile <- readCabalFile cabalFileName
let
newCabalFile = makeCabalFile generateHashStrategy mExistingCabalFile cabalVersion v pkg

status = case force of
Force -> Generated
NoForce -> maybe Generated (mkStatus newCabalFile) mExistingCabalFile

case status of
Generated -> writeCabalFile options toStdout cabalFileName newCabalFile
_ -> return ()

return $ Right $ Result {
resultWarnings = warnings
, resultCabalFile = cabalFileName
, resultStatus = status
}
Left e -> return $ Left e

writeCabalFile :: DecodeOptions -> Bool -> FilePath -> CabalFile -> IO ()
writeCabalFile options toStdout name cabalFile = do
Expand Down
83 changes: 39 additions & 44 deletions src/Hpack/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ module Hpack.Config (
, packageConfig
, DecodeResult(..)
, readPackageConfig
, readPackageConfigWithError

, renamePackage
, packageDependencies
Expand Down Expand Up @@ -112,6 +113,7 @@ import Data.Aeson.Config.Types
import Data.Aeson.Config.FromValue hiding (decodeValue)
import qualified Data.Aeson.Config.FromValue as Config

import Hpack.Error
import Hpack.Syntax.Defaults
import Hpack.Util hiding (expandGlobs)
import qualified Hpack.Util as Util
Expand Down Expand Up @@ -631,13 +633,13 @@ type ParsePackageConfig = PackageConfigWithDefaults ParseCSources ParseCxxSource
instance FromValue ParsePackageConfig

type Warnings m = WriterT [String] m
type Errors = ExceptT String
type Errors = ExceptT HpackError

decodeYaml :: FromValue a => ProgramName -> FilePath -> Warnings (Errors IO) a
decodeYaml programName file = do
(warnings, a) <- lift (ExceptT $ Yaml.decodeYaml file)
decodeYaml :: FromValue a => FilePath -> Warnings (Errors IO) a
decodeYaml file = do
(warnings, a) <- lift (ExceptT $ first HpackParseYamlException <$> Yaml.decodeYaml file)
tell warnings
decodeValue programName file a
decodeValue file a

data DecodeOptions = DecodeOptions {
decodeOptionsProgramName :: ProgramName
Expand All @@ -646,12 +648,6 @@ data DecodeOptions = DecodeOptions {
, decodeOptionsDecode :: FilePath -> IO (Either String ([String], Value))
}

newtype ProgramName = ProgramName String
deriving (Eq, Show)

instance IsString ProgramName where
fromString = ProgramName

defaultDecodeOptions :: DecodeOptions
defaultDecodeOptions = DecodeOptions "hpack" packageConfig Nothing Yaml.decodeYaml

Expand All @@ -663,13 +659,16 @@ data DecodeResult = DecodeResult {
} deriving (Eq, Show)

readPackageConfig :: DecodeOptions -> IO (Either String DecodeResult)
readPackageConfig (DecodeOptions programName file mUserDataDir readValue) = runExceptT $ fmap addCabalFile . runWriterT $ do
(warnings, value) <- lift . ExceptT $ readValue file
readPackageConfig options = first (renderHpackError $ decodeOptionsProgramName options) <$> readPackageConfigWithError options

readPackageConfigWithError :: DecodeOptions -> IO (Either HpackError DecodeResult)
readPackageConfigWithError (DecodeOptions _ file mUserDataDir readValue) = runExceptT $ fmap addCabalFile . runWriterT $ do
(warnings, value) <- lift . ExceptT $ first HpackParseYamlException <$> readValue file
tell warnings
config <- decodeValue programName file value
config <- decodeValue file value
dir <- liftIO $ takeDirectory <$> canonicalizePath file
userDataDir <- liftIO $ maybe (getAppUserDataDirectory "hpack") return mUserDataDir
toPackage programName userDataDir dir config
userDataDir <- liftIO $ maybe (getAppUserDataDirectory $ unProgramName hpackProgName) return mUserDataDir
toPackage userDataDir dir config
where
addCabalFile :: ((Package, String), [String]) -> DecodeResult
addCabalFile ((pkg, cabalVersion), warnings) = DecodeResult pkg cabalVersion (takeDirectory_ file </> (packageName pkg ++ ".cabal")) warnings
Expand Down Expand Up @@ -890,12 +889,12 @@ determineCabalVersion inferredLicense pkg@Package{..} = (
sectionAll :: (Semigroup b, Monoid b) => (Section a -> b) -> Section a -> b
sectionAll f sect = f sect <> foldMap (foldMap $ sectionAll f) (sectionConditionals sect)

decodeValue :: FromValue a => ProgramName -> FilePath -> Value -> Warnings (Errors IO) a
decodeValue (ProgramName programName) file value = do
(r, unknown, deprecated) <- lift . ExceptT . return $ first (prefix ++) (Config.decodeValue value)
decodeValue :: FromValue a => FilePath -> Value -> Warnings (Errors IO) a
decodeValue file value = do
(r, unknown, deprecated) <- lift . ExceptT . return $ first (DecodeValueError file) (Config.decodeValue value)
case r of
UnsupportedSpecVersion v -> do
lift $ throwE ("The file " ++ file ++ " requires version " ++ showVersion v ++ " of the Hpack package specification, however this version of " ++ programName ++ " only supports versions up to " ++ showVersion Hpack.version ++ ". Upgrading to the latest version of " ++ programName ++ " may resolve this issue.")
lift $ throwE $ HpackVersionUnsupported file v Hpack.version
SupportedSpecVersion a -> do
tell (map formatUnknownField unknown)
tell (map formatDeprecatedField deprecated)
Expand Down Expand Up @@ -1049,9 +1048,9 @@ type ConfigWithDefaults = Product
type CommonOptionsWithDefaults a = Product DefaultsConfig (CommonOptions ParseCSources ParseCxxSources ParseJsSources a)
type WithCommonOptionsWithDefaults a = Product DefaultsConfig (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a)

toPackage :: ProgramName -> FilePath -> FilePath -> ConfigWithDefaults -> Warnings (Errors IO) (Package, String)
toPackage programName userDataDir dir =
expandDefaultsInConfig programName userDataDir dir
toPackage :: FilePath -> FilePath -> ConfigWithDefaults -> Warnings (Errors IO) (Package, String)
toPackage userDataDir dir =
expandDefaultsInConfig userDataDir dir
>=> setDefaultLanguage "Haskell2010"
>>> traverseConfig (expandForeignSources dir)
>=> toPackage_ dir
Expand All @@ -1061,35 +1060,32 @@ toPackage programName userDataDir dir =
setLanguage = (mempty { commonOptionsLanguage = Alias . Last $ Just (Just language) } <>)

expandDefaultsInConfig
:: ProgramName
-> FilePath
:: FilePath
-> FilePath
-> ConfigWithDefaults
-> Warnings (Errors IO) (Config ParseCSources ParseCxxSources ParseJsSources)
expandDefaultsInConfig programName userDataDir dir = bitraverse (expandGlobalDefaults programName userDataDir dir) (expandSectionDefaults programName userDataDir dir)
expandDefaultsInConfig userDataDir dir = bitraverse (expandGlobalDefaults userDataDir dir) (expandSectionDefaults userDataDir dir)

expandGlobalDefaults
:: ProgramName
-> FilePath
:: FilePath
-> FilePath
-> CommonOptionsWithDefaults Empty
-> Warnings (Errors IO) (CommonOptions ParseCSources ParseCxxSources ParseJsSources Empty)
expandGlobalDefaults programName userDataDir dir = do
fmap (`Product` Empty) >>> expandDefaults programName userDataDir dir >=> \ (Product c Empty) -> return c
expandGlobalDefaults userDataDir dir = do
fmap (`Product` Empty) >>> expandDefaults userDataDir dir >=> \ (Product c Empty) -> return c

expandSectionDefaults
:: ProgramName
-> FilePath
:: FilePath
-> FilePath
-> PackageConfigWithDefaults ParseCSources ParseCxxSources ParseJsSources
-> Warnings (Errors IO) (PackageConfig ParseCSources ParseCxxSources ParseJsSources)
expandSectionDefaults programName userDataDir dir p@PackageConfig{..} = do
library <- traverse (expandDefaults programName userDataDir dir) packageConfigLibrary
internalLibraries <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigInternalLibraries
executable <- traverse (expandDefaults programName userDataDir dir) packageConfigExecutable
executables <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigExecutables
tests <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigTests
benchmarks <- traverse (traverse (expandDefaults programName userDataDir dir)) packageConfigBenchmarks
expandSectionDefaults userDataDir dir p@PackageConfig{..} = do
library <- traverse (expandDefaults userDataDir dir) packageConfigLibrary
internalLibraries <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigInternalLibraries
executable <- traverse (expandDefaults userDataDir dir) packageConfigExecutable
executables <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigExecutables
tests <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigTests
benchmarks <- traverse (traverse (expandDefaults userDataDir dir)) packageConfigBenchmarks
return p{
packageConfigLibrary = library
, packageConfigInternalLibraries = internalLibraries
Expand All @@ -1101,12 +1097,11 @@ expandSectionDefaults programName userDataDir dir p@PackageConfig{..} = do

expandDefaults
:: (FromValue a, Semigroup a, Monoid a)
=> ProgramName
-> FilePath
=> FilePath
-> FilePath
-> WithCommonOptionsWithDefaults a
-> Warnings (Errors IO) (WithCommonOptions ParseCSources ParseCxxSources ParseJsSources a)
expandDefaults programName userDataDir = expand []
expandDefaults userDataDir = expand []
where
expand :: (FromValue a, Semigroup a, Monoid a) =>
[FilePath]
Expand All @@ -1126,14 +1121,14 @@ expandDefaults programName userDataDir = expand []
file <- lift $ ExceptT (ensure userDataDir dir defaults)
seen_ <- lift (checkCycle seen file)
let dir_ = takeDirectory file
decodeYaml programName file >>= expand seen_ dir_
decodeYaml file >>= expand seen_ dir_

checkCycle :: [FilePath] -> FilePath -> Errors IO [FilePath]
checkCycle seen file = do
canonic <- liftIO $ canonicalizePath file
let seen_ = canonic : seen
when (canonic `elem` seen) $ do
throwE ("cycle in defaults (" ++ intercalate " -> " (reverse seen_) ++ ")")
throwE $ CycleInDefaultsError $ reverse seen_
return seen_

toExecutableMap :: Monad m => String -> Maybe (Map String a) -> Maybe a -> Warnings m (Maybe (Map String a))
Expand Down
19 changes: 7 additions & 12 deletions src/Hpack/Defaults.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,10 @@ import Network.HTTP.Types
import Network.HTTP.Client
import Network.HTTP.Client.TLS
import qualified Data.ByteString.Lazy as LB
import qualified Data.ByteString.Char8 as B
import System.FilePath
import System.Directory

import Hpack.Error (HpackError (..))
import Hpack.Syntax.Defaults

type URL = String
Expand All @@ -33,7 +33,7 @@ defaultsCachePath :: FilePath -> Github -> FilePath
defaultsCachePath dir Github{..} = joinPath $
dir : "defaults" : githubOwner : githubRepo : githubRef : githubPath

data Result = Found | NotFound | Failed String
data Result = Found | NotFound | Failed URL Status
deriving (Eq, Show)

get :: URL -> FilePath -> IO Result
Expand All @@ -47,27 +47,22 @@ get url file = do
LB.writeFile file (responseBody response)
return Found
Status 404 _ -> return NotFound
status -> return (Failed $ "Error while downloading " ++ url ++ " (" ++ formatStatus status ++ ")")
status -> return (Failed url status)

formatStatus :: Status -> String
formatStatus (Status code message) = show code ++ " " ++ B.unpack message

ensure :: FilePath -> FilePath -> Defaults -> IO (Either String FilePath)
ensure :: FilePath -> FilePath -> Defaults -> IO (Either HpackError FilePath)
ensure userDataDir dir = \ case
DefaultsGithub defaults -> do
let
url = defaultsUrl defaults
file = defaultsCachePath userDataDir defaults
ensureFile file url >>= \ case
Found -> return (Right file)
NotFound -> return (Left $ notFound url)
Failed err -> return (Left err)
NotFound -> return (Left $ DefaultsFileUrlNotFound url)
Failed url' status -> return (Left $ DownloadingFileFailed url' status)
DefaultsLocal (Local ((dir </>) -> file)) -> do
doesFileExist file >>= \ case
True -> return (Right file)
False -> return (Left $ notFound file)
where
notFound file = "Invalid value for \"defaults\"! File " ++ file ++ " does not exist!"
False -> return (Left $ DefaultsFileNotFound file)

ensureFile :: FilePath -> URL -> IO Result
ensureFile file url = do
Expand Down
Loading

0 comments on commit be187b1

Please sign in to comment.