[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: get-win32-tarballs.py: List tarball files to be downloaded if we cannot find them

Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: ed5a675e by Zubin Duggal at 2025-04-30T00:15:35-04:00 get-win32-tarballs.py: List tarball files to be downloaded if we cannot find them Fixes #25929 - - - - - 319b4d10 by Ben Gamari at 2025-04-30T00:15:36-04:00 Move Data ModuleName instance to Language.Haskell.Syntax.Module.Name Fixes #25968. - - - - - 3 changed files: - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Module/Name.hs - m4/fp_setup_windows_toolchain.m4 Changes: ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-orphans #-} -- instance Data ModuleName - {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveTraversable #-} @@ -117,13 +115,6 @@ data GenModule unit = Module } deriving (Eq,Ord,Data,Functor) --- TODO: should be moved back into Language.Haskell.Syntax.Module.Name -instance Data ModuleName where - -- don't traverse? - toConstr _ = abstractConstr "ModuleName" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "ModuleName" - -- | A Module is a pair of a 'Unit' and a 'ModuleName'. type Module = GenModule Unit ===================================== compiler/Language/Haskell/Syntax/Module/Name.hs ===================================== @@ -3,6 +3,7 @@ module Language.Haskell.Syntax.Module.Name where import Prelude import Data.Char (isAlphaNum) +import Data.Data import Control.DeepSeq import qualified Text.ParserCombinators.ReadP as Parse import System.FilePath @@ -12,6 +13,14 @@ import GHC.Data.FastString -- | A ModuleName is essentially a simple string, e.g. @Data.List@. newtype ModuleName = ModuleName FastString deriving (Show, Eq) +instance Data ModuleName where + -- don't traverse? + toConstr x = constr + where + constr = mkConstr (dataTypeOf x) "{abstract:ModuleName}" [] Prefix + gunfold _ _ = error "gunfold" + dataTypeOf _ = mkNoRepType "ModuleName" + instance Ord ModuleName where nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2 ===================================== m4/fp_setup_windows_toolchain.m4 ===================================== @@ -17,12 +17,13 @@ AC_DEFUN([FP_INSTALL_WINDOWS_TOOLCHAIN],[ else action="download" fi - $PYTHON mk/get-win32-tarballs.py $action $mingw_arch > missing-win32-tarballs + $PYTHON mk/get-win32-tarballs.py $action $mingw_arch case $? in 0) rm missing-win32-tarballs ;; 2) + $PYTHON mk/get-win32-tarballs.py list $mingw_arch > missing-win32-tarballs echo echo "Error:" echo "Needed msys2 tarballs are missing. You have a few options to get them," View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3787f53398217a3d8494cbc2c94f04c... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3787f53398217a3d8494cbc2c94f04c... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)